Why no logical ==?

The mistake is not with the inclusion of an operator toward logical equivalence in the Fortran standard.

It was actually a good thing for practitioners that starting FORTRAN 77, the language added logical equivalence operators.

The mistake indeed by the ANSI X3.9 committee working on FORTRAN 77 is with using a separate operator in the form of .EQV. instead of overloading .EQ. with the LOGICAL type .(and its counterpart in .NEQV. vs .NE.)

And by X3J3 committee working on Fortran 90 for furthering the issue with the == operator.

Fortran compilers support multiple KINDs of integers, and comparing two integer variables with different kinds works as expected. The user does not think about how the compiler represents integers under the hood. If one were starting from scratch, I think Fortran logical variables should work the same way.

3 Likes

So, per the semantics in the standard, they do.

The issue is with .EQV. and .NEQV., they were not needed. Starting FORTRAN 77, the existing .EQ. and .NE. intrinsic operators could have been overloaded to work with the LOGICAL type, the way it was done with CHARACTER type.

Or, at least by Fortran 90, == and /= could have been made to work.

Now the situation is worse than that of dealing with an entrenched bureaucracy to try to do anything and that’s the shame.

@sblionel ,
Thanks for your article ( and all your thoughtful articles), but on this one I do have some disagrerement.

For logical, there are two constants, .TRUE. and .FALSE. To quote that too frequent annoying cop-out in the Fortran standards, their bit patterns are ā€œprocessor dependentā€.

If I consistently use these constants to define the value or use of logical variables, I would expect that ā€œIF (LOGVAL1 .EQ. LOGVAL2)ā€ to give a correct interpretation, irrespective of the hardware interpretation. As such, I seen no problem with using .EQ. or .NE. ( or == and /= )

Also you state: ā€œā€œI use .AND. and .OR . on integers all the time!ā€ And so you doā€
? I disagree, never !!
I would be much more likely to use ā€œ(LOGVAL1 .EQ. LOGVAL2)ā€, than ā€œ(IVAL1 .AND. IVAL2)ā€, as why would I want a logical result from ā€œandā€ or ā€œorā€ of two integers ? ( I would probably have used an intrinsic bit functions more often than .EQV. )

I think .EQ. or .NE. ( or == and /= ) is a reasonable and clear extension, rather than the rarely used .EQV. or .NEQV., as the result remains a consistent logical type. If the logical variables have obtained their value, in a way that is not consistent with the hardware implementation of .TRUE. or .FALSE., then it is reasonable that the result is ā€œprocessor dependentā€.

Being ā€œprocessor dependentā€ is a far more likely problem for programmers than the need for .EQV. or .NEQV. !!

In 50 years of using Fortran, I can’t recall ever coding with .NEQV., except for reviewing a forum coding question.

Then there are the questions about the use of " IF ( IVAL = JVAL ) …" or " i = 2^n", both of which compilers find as a syntax error, but should a modern ā€œsmartā€ compilers do better ?

Agree, and I don’t get at all what the internal representations of logicals have to do with the topic of comparing logicals.

It was not a mistake, It was probably what appeared a logical choice because of the precedence issue between .EQ. and the boolean operators.

I can’t see at all what x86 (*) or whatever other platform has to do with the current discussion about comparing logical variables. Fortran standards were designed to be portable and platform-agnostic.

Also, I’m a bit skeptic (to say the least) about your considerations about analog computers

  • by the time the F77 standard arose with the .EQV. operator, it seems that analog computers were long superseded by digital ones
  • it has to do with internal representation, and once again the standard doesn’t deal with internal representations. Whether a logical .true. is a 32 bits word with only the least one at 1, or the least one at 1 whatever the othe ones, or any other choice, or an analog value between +2 and +4 volts, or whatever, does not matter at all.

(*) BTW, x86 has long been an ā€œEnterprise Computingā€ friend

Re: " It was probably what appeared a logical choice because of the precedence issue between .EQ. and the boolean operators."

The precedence issue was the effect of the choice with the .EQV. operator and a bad one at that that.

Thus no, it was a mistake.

(edit: originally this post was answering @seasoned_geek , but I see now that his posts have been flagged and hidden, so I have removed my answers in order to end this unproductive discussion)

So we disagree here.

I certainly wasn’t on the committee when FORTRAN 66 was standardized, so I don’t have insight into motivations, but I don’t consider it a mistake for LOGICAL to have its own operators, with their own precedence. What I do consider a mistake is all this kvetching over a language feature that isn’t wrong, isn’t a bad practice, but is simply surprising to some people. It’s not as if the standard lets you get away with misusing .EQ. and .NEQ. here - it’s the compilers that chose to extend the language and permit that use that led to possible confusion.

The Fortran standard goes to great lengths to not tie itself to a particular hardware implementation - that’s one of its major strengths. I see zero advantage to changing the equality operators to also cover LOGICAL and am baffled at the energy being poured into this argument, much as I am with other windmill-tilts such as changing the meaning of file types (again, not a standards issue) or deleting features. Some of the loudest voices here are constantly bemoaning the lack of new features in the language but spend much of their energy trying to relitigate the past instead.

If you really care about Fortran and want it to continue to succeed, stop throwing rocks and start developing NEW ideas. (Yes, I know some of you are contributing a lot, and I thank you.)

As for my Doctor Fortran post referenced in this thread, I write these from the standard’s perspective and also my decades of experience doing support for Fortran compiler users. No, not everyone engages in bad practices enabled by extensions, but many do. Let’s not make it worse.

9 Likes

So you are essentially saying that because of internal representation issues .eq. could not compare logical variables, but .eqv. can… A magic effect of the v letter??

x86 does not imply that at all. How a logical is represented in memory is compiler dependent, not platform dependent. By the way, ifort and gfortran on x86 do not represent .true. the same way.

1 Like

@seasoned geek said you cannot have ==. But if you really want it for type logical you can always overload it, as in this little program based on one testing a different aspect of .eqv. by @kargl.

program foo
  implicit none
  interface operator(==)
     procedure eq12, eq21
  end interface operator(==)
  character(*), parameter :: fmt = '(A,2L2,3I2)'
   logical(1) a1  ! nonportable gfortran kind=1 value
   logical(2) a2  ! nonportable gfortran kind=2 value
   a1 = .true._1
   a2 = .true._2
   if (a1.eqv.a2) print fmt,'a1.eqv.a2',a1,a2,kind(a1),kind(a2),kind(a1.eqv.a2)
   if (a2.eqv.a1) print fmt,'a2.eqv.a1',a2,a1,kind(a2),kind(a1),kind(a2.eqv.a1)
   if (a1 == a2)  print fmt, 'a1 == a2',  a1,a2,kind(a1), kind(a2),kind(a1==a2)
   if (a2 == a1)  print fmt, 'a2 == a1',  a2,a1,kind(a2), kind(a1),kind(a2==a1)
 contains
   logical(2) function eq12(p,q)
     logical(1),intent(in)::p
     logical(2),intent(in)::  q
     eq12 = p.EQV.q
   end function eq12
   logical(2) function eq21(p,q) !
     logical(2),intent(in)::p
     logical(1),intent(in)::  q
     eq21 = p.EQV.q
   end function eq21
 end program foo

That compiled and ran in my x86_64 Ubuntu system with both gfortran and ifort, giving the same output What surprised me was that the kind type parameter value of the result of a logical intrinsic binary operation is processor dependent (see f2023 A.2), so I had to guess whether to declare the functions eq12 and eq21 as logical(1) or logical(2).

If you want to do such things yourself, you should check how the precedence rules work for.eqv. and ==

Steve, I asked the question ā€œshould a modern ā€œsmartā€ compilers do better ?ā€

I don’t think this is throwing rocks, or a trivial question.

Thank you for being rather kind and courteous and not saying what should have been said which was to ā€œgrow some skin, would you?ā€

That entire post with ā€œstop throwing rocks and start developing NEW ideasā€ is utter nonsense for any number of reasons but importantly:

  1. all this thread is discourse which is what this forum is all about. If someone can’t stomach that, then don’t read it, period. But no one has the goddamn right to try to stop the discourse just because the standard and its committees get shown up where the Fortran practitioners were most poorly served. The poster had just posted in another thread a supposed case for Fortran to continue, when convenient, to avoid making some changes in the name of backward compatibility. It was on the basis of a criticism of C standard revision for 2023 but where the article also included the following and it is exactly what this thread addresses:

  2. Any number of ideas to improve the Fortran language are constantly passed on to the committee, in communique after communique, paper after paper, forum post after another, many ideas repeated multiple times. All that committee consents to do is too little, too late. Everything is ā€œminus 100 pointsā€ and when practitioners feedback ideas, there is the excuse of ā€œlanguage bloatā€ but then the very same cast of characters add, of all things, TWO DIFFERENT ENUM TYPES to the language, neither of which are all that functional and useful in year 2023!!! Who does that?

To build on the questions raised by @JohnCampbell , consider the following snippet:

   integer :: a = 1, b = 2
   integer :: u = -1, v = -1
   logical :: x = .false., y = .false.
   print *, "a==b .and. u==v?", a==b .and. u==v
   print *, "a==b .and. x==y?", a==b .and. x==y
   print *, "a==b .and. x.eqv.y?", a==b .and. x.eqv.y
end
  • where with Digital Fortran decades ago or with Intel Fortran now, the program response will be
C:\temp>ifort /free p.f
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.8.0 Build 20221119_000000
Copyright (C) 1985-2022 Intel Corporation.  All rights reserved.

Microsoft (R) Incremental Linker Version 14.34.31937.0
Copyright (C) Microsoft Corporation.  All rights reserved.

-out:p.exe
-subsystem:console
p.obj

C:\temp>p.exe
 a==b .and. u==v? F
 a==b .and. x==y? F
 a==b .and. x.eqv.y? T

(anyone curious and doubtful can retry this with .EQ. instead of ==)
and this is sheer nonsense, making a mockery of the practitioners and wasting their valuable time.

There is no logical explanation anyone can provide as to why the language needed a separate .EQV. operator back when it was introduced in ANSI X3.9 1978 document and why it needed a different precedence below .EQ. and .AND.. This is the mistake. And this is not throwing rocks, simply having a discourse about it.

The explanation has been given in this thread, and it makes sense. That you disagree or don’t like is another issue.

Constantly talking about ā€œmistakesā€ and inability to correct them is just meaning that these people are dumb.

I’m not certain, but I think .eqv. and .neqv. were already common fortran extensions before f77. That is, I think f77 was standardizing common existing practice, it was not inventing new syntax out of thin air. Does anyone have any pre-f77 compiler documentation to verify that conjecture?

The compiler manuals section of the Fortran Wiki has some older manuals:

If people know of others, please add them to the wiki or post here. I don’t see .eqv in the 4K manual.

2 Likes

Consider ā€œIBM Series/1 FORTRAN IV Language Referenceā€ dated February 1977, that did not include any extension of the .EQV. type.

I used a later version of that compiler (for DECSYSTEM-20 and TOPS-20) starting about 1976, and I think I remember using .eqv. then, but I wasn’t sure.

For that IBM compiler, how was one supposed to test logical variables for equivalence? Was there an extension for .eq., or was there another operator one was supposed to use?

Way, way, way before my time! My hunch would be the programmers either worked with integers only (most likely) or (less common) wrote their own code with the truth table they wanted to follow in conjunction with the supported .AND., .OR. operators on objects of LOGICAL type in the language.

Wow, this is an interesting read. This fortran had no logical variables at all, much less logical operators to compare them. There is also no logical IF statement, even for comparison of integers or reals. The only IF statement is the 3-way arithmetic statement. Lots of other weird stuff too.