public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/65454] New: Extending both forms of relational operators
@ 2015-03-17 16:00 wxcvbn789456123-nw6wda at yahoo dot fr
  2015-03-20  9:59 ` [Bug fortran/65454] " dominiq at lps dot ens.fr
                   ` (5 more replies)
  0 siblings, 6 replies; 7+ messages in thread
From: wxcvbn789456123-nw6wda at yahoo dot fr @ 2015-03-17 16:00 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=65454

            Bug ID: 65454
           Summary: Extending both forms of relational operators
           Product: gcc
           Version: 4.9.2
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
          Assignee: unassigned at gcc dot gnu.org
          Reporter: wxcvbn789456123-nw6wda at yahoo dot fr

Extending both forms of relational operators

Dear Sirs,

The F2008 Working Document, J3/12-007, states in 12.4.3.4.2 Defined operations:

"Because both forms of each relational operator have the same interpretation
(7.1.6.2), extending one form (such as <=) has the effect of defining both
forms (<= and .LE.)."

However, the following program does not compile with gfortran.
This problem does not occur with ifort.

Operating system = Microsoft Windows 7 SP1
gfortran: provided by cygwin

Example under a Cygwin session:

bash 1 : uname -smo
CYGWIN_NT-6.1-WOW i686 Cygwin
bash 2 : gfortran --version | head -3
GNU Fortran (GCC) 4.9.2
Copyright (C) 2014 Free Software Foundation, Inc.

bash 3 : cat oper.f90

MODULE deriv_m
   IMPLICIT NONE
   TYPE deriv_t
      INTEGER :: i
   END TYPE deriv_t
   INTERFACE OPERATOR (<=)
      MODULE PROCEDURE :: deriv_LE_deriv
   END INTERFACE OPERATOR (<=)
CONTAINS
   ELEMENTAL FUNCTION deriv_LE_deriv (a, b) RESULT (c)
      TYPE(deriv_t), INTENT(IN) :: a, b
      LOGICAL                   :: c
      c = a%i .LE. b%i
   END FUNCTION deriv_LE_deriv
END MODULE deriv_m

PROGRAM oper
   USE :: deriv_m, ONLY: deriv_t, OPERATOR(.LE.)
   IMPLICIT NONE
   TYPE(deriv_t) :: one = deriv_t(1), two = deriv_t(2)
   WRITE (*,'(A,L1)') '(one  <=  two) = ', one  <=  two
   WRITE (*,'(A,L1)') '(one .LE. two) = ', one .LE. two
END PROGRAM oper

bash 4 : gfortran oper.f90 -o g.exe
oper.f90:19.33:

   USE :: deriv_m, ONLY: deriv_t, OPERATOR(.LE.)
                                 1
Error: Intrinsic operator '.le.' referenced at (1) not found in module
'deriv_m'
oper.f90:22.42:

   WRITE (*,'(A,L1)') '(one  <=  two) = ', one  <=  two
                                          1
Error: Operands of comparison operator '<=' at (1) are
TYPE(deriv_t)/TYPE(deriv_t)
oper.f90:23.42:

   WRITE (*,'(A,L1)') '(one .LE. two) = ', one .LE. two
                                          1
Error: Operands of comparison operator '.le.' at (1) are
TYPE(deriv_t)/TYPE(deriv_t)

bash 5 : ifort /nologo oper.f90 /exe:i.exe
bash 6 : ./i.exe
(one  <=  two) = T
(one .LE. two) = T


Can this behavior be considered as a bug?

Greetings

Paul


^ permalink raw reply	[flat|nested] 7+ messages in thread

* [Bug fortran/65454] Extending both forms of relational operators
  2015-03-17 16:00 [Bug fortran/65454] New: Extending both forms of relational operators wxcvbn789456123-nw6wda at yahoo dot fr
@ 2015-03-20  9:59 ` dominiq at lps dot ens.fr
  2015-08-29 13:55 ` dominiq at lps dot ens.fr
                   ` (4 subsequent siblings)
  5 siblings, 0 replies; 7+ messages in thread
From: dominiq at lps dot ens.fr @ 2015-03-20  9:59 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=65454

Dominique d'Humieres <dominiq at lps dot ens.fr> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |WAITING
   Last reconfirmed|                            |2015-03-20
     Ever confirmed|0                           |1

--- Comment #2 from Dominique d'Humieres <dominiq at lps dot ens.fr> ---
> > Can this behavior be considered as a bug?
>
> I'm not completely sure, but probably yes.

Not sure either.

> A workaround is to apply the USE directive without the ONLY. 

The code compiles and gives the "expected" result at run time if the line

   USE :: deriv_m, ONLY: deriv_t, OPERATOR(.LE.)

is replaced with

   USE :: deriv_m, ONLY: deriv_t, operator(<=)

> Also, the latter possibly makes your program invalid, since you import
> only the ".LE." but not the "<=" operator. Or should it import both forms?

I don't understand the above sentences.

> (I haven't read up on the details in the standard.)

I had a look, but did not find anything related to USE...ONLY (I did not look
too hard!-).


^ permalink raw reply	[flat|nested] 7+ messages in thread

* [Bug fortran/65454] Extending both forms of relational operators
  2015-03-17 16:00 [Bug fortran/65454] New: Extending both forms of relational operators wxcvbn789456123-nw6wda at yahoo dot fr
  2015-03-20  9:59 ` [Bug fortran/65454] " dominiq at lps dot ens.fr
@ 2015-08-29 13:55 ` dominiq at lps dot ens.fr
  2021-09-12 19:37 ` anlauf at gcc dot gnu.org
                   ` (3 subsequent siblings)
  5 siblings, 0 replies; 7+ messages in thread
From: dominiq at lps dot ens.fr @ 2015-08-29 13:55 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=65454

--- Comment #3 from Dominique d'Humieres <dominiq at lps dot ens.fr> ---
Could this PR be closed as INVALID?


^ permalink raw reply	[flat|nested] 7+ messages in thread

* [Bug fortran/65454] Extending both forms of relational operators
  2015-03-17 16:00 [Bug fortran/65454] New: Extending both forms of relational operators wxcvbn789456123-nw6wda at yahoo dot fr
  2015-03-20  9:59 ` [Bug fortran/65454] " dominiq at lps dot ens.fr
  2015-08-29 13:55 ` dominiq at lps dot ens.fr
@ 2021-09-12 19:37 ` anlauf at gcc dot gnu.org
  2021-10-08 21:35 ` anlauf at gcc dot gnu.org
                   ` (2 subsequent siblings)
  5 siblings, 0 replies; 7+ messages in thread
From: anlauf at gcc dot gnu.org @ 2021-09-12 19:37 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=65454

anlauf at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Keywords|                            |rejects-valid
                 CC|                            |anlauf at gcc dot gnu.org
   Last reconfirmed|2015-03-20 00:00:00         |2021-9-12
             Status|WAITING                     |NEW

--- Comment #5 from anlauf at gcc dot gnu.org ---
F2018 clearly states:

10.1.5.5.1  Interpretation of relational intrinsic operations

The operators <, <=, >, >=, ==, and /= always have the same interpretations as
the operators .LT., .LE., .GT., .GE., .EQ., and .NE., respectively.

We need to handle this.

(The current gfortran code seems to be able to distinguish between "old-style"
and "new-style" and may fail to handle source code such as in this PR.)

^ permalink raw reply	[flat|nested] 7+ messages in thread

* [Bug fortran/65454] Extending both forms of relational operators
  2015-03-17 16:00 [Bug fortran/65454] New: Extending both forms of relational operators wxcvbn789456123-nw6wda at yahoo dot fr
                   ` (2 preceding siblings ...)
  2021-09-12 19:37 ` anlauf at gcc dot gnu.org
@ 2021-10-08 21:35 ` anlauf at gcc dot gnu.org
  2021-10-09 19:16 ` cvs-commit at gcc dot gnu.org
  2021-10-09 19:19 ` anlauf at gcc dot gnu.org
  5 siblings, 0 replies; 7+ messages in thread
From: anlauf at gcc dot gnu.org @ 2021-10-08 21:35 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=65454

anlauf at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
   Last reconfirmed|2021-09-12 00:00:00         |2021-10-8
           Assignee|unassigned at gcc dot gnu.org      |anlauf at gcc dot gnu.org
             Status|NEW                         |ASSIGNED

--- Comment #6 from anlauf at gcc dot gnu.org ---
Patch: https://gcc.gnu.org/pipermail/fortran/2021-October/056681.html

^ permalink raw reply	[flat|nested] 7+ messages in thread

* [Bug fortran/65454] Extending both forms of relational operators
  2015-03-17 16:00 [Bug fortran/65454] New: Extending both forms of relational operators wxcvbn789456123-nw6wda at yahoo dot fr
                   ` (3 preceding siblings ...)
  2021-10-08 21:35 ` anlauf at gcc dot gnu.org
@ 2021-10-09 19:16 ` cvs-commit at gcc dot gnu.org
  2021-10-09 19:19 ` anlauf at gcc dot gnu.org
  5 siblings, 0 replies; 7+ messages in thread
From: cvs-commit at gcc dot gnu.org @ 2021-10-09 19:16 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=65454

--- Comment #7 from CVS Commits <cvs-commit at gcc dot gnu.org> ---
The master branch has been updated by Harald Anlauf <anlauf@gcc.gnu.org>:

https://gcc.gnu.org/g:b2713e9f16d3f3597d71e4be6384ecd788684936

commit r12-4274-gb2713e9f16d3f3597d71e4be6384ecd788684936
Author: Harald Anlauf <anlauf@gmx.de>
Date:   Sat Oct 9 21:16:32 2021 +0200

    Fortran: accept both old and new-style relational operators in USE, ONLY

    F2018:10.1.5.5.1(2) requires the same interpretation of old and new-style
    relational operators.  As gfortran internally distinguishes between
    these versions, we must match equivalent notations in
            USE module, ONLY: OPERATOR(op)
    statements when reading modules.

    gcc/fortran/ChangeLog:

            PR fortran/65454
            * module.c (read_module): Handle old and new-style relational
            operators when used in USE module, ONLY: OPERATOR(op).

    gcc/testsuite/ChangeLog:

            PR fortran/65454
            * gfortran.dg/interface_operator_3.f90: New test.

^ permalink raw reply	[flat|nested] 7+ messages in thread

* [Bug fortran/65454] Extending both forms of relational operators
  2015-03-17 16:00 [Bug fortran/65454] New: Extending both forms of relational operators wxcvbn789456123-nw6wda at yahoo dot fr
                   ` (4 preceding siblings ...)
  2021-10-09 19:16 ` cvs-commit at gcc dot gnu.org
@ 2021-10-09 19:19 ` anlauf at gcc dot gnu.org
  5 siblings, 0 replies; 7+ messages in thread
From: anlauf at gcc dot gnu.org @ 2021-10-09 19:19 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=65454

anlauf at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
         Resolution|---                         |FIXED
   Target Milestone|---                         |12.0
             Status|ASSIGNED                    |RESOLVED

--- Comment #8 from anlauf at gcc dot gnu.org ---
Fixed for gcc-12.  Closing.

Thanks for the report!

^ permalink raw reply	[flat|nested] 7+ messages in thread

end of thread, other threads:[~2021-10-09 19:19 UTC | newest]

Thread overview: 7+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2015-03-17 16:00 [Bug fortran/65454] New: Extending both forms of relational operators wxcvbn789456123-nw6wda at yahoo dot fr
2015-03-20  9:59 ` [Bug fortran/65454] " dominiq at lps dot ens.fr
2015-08-29 13:55 ` dominiq at lps dot ens.fr
2021-09-12 19:37 ` anlauf at gcc dot gnu.org
2021-10-08 21:35 ` anlauf at gcc dot gnu.org
2021-10-09 19:16 ` cvs-commit at gcc dot gnu.org
2021-10-09 19:19 ` anlauf at gcc dot gnu.org

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).