public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/33542]  New: gfortran does not detect ambigious specific names if they are the same as generic names
@ 2007-09-24  9:06 burnus at gcc dot gnu dot org
  2007-09-24 20:55 ` [Bug fortran/33542] " burnus at gcc dot gnu dot org
                   ` (9 more replies)
  0 siblings, 10 replies; 11+ messages in thread
From: burnus at gcc dot gnu dot org @ 2007-09-24  9:06 UTC (permalink / raw)
  To: gcc-bugs

Found at
http://groups.google.com/group/comp.lang.fortran/browse_thread/thread/1abc1549a6a164f1/

One should re-check it as only g95 and Portland reject it whereas Pathscale,
gfortran, ifort, sunf95,openf95 and especially NAG f95 and Lahey accept it.

The following program is obviously wrong as one tries to pass an generic name
as actual argument, which is not possible as only specific names are allow.
gfortran and the other compilers properly diagnose:

Error: GENERIC non-INTRINSIC procedure 'foo' is not allowed as an actual
argument at (1)

for the following program:

MODULE M1
   INTERFACE FOO
     MODULE PROCEDURE FOO2
   END INTERFACE
CONTAINS
   SUBROUTINE FOO2(I)
     INTEGER, INTENT(IN) :: I
     WRITE(*,*) 'INTEGER'
   END SUBROUTINE FOO2
END MODULE M1

MODULE M2
   INTERFACE FOO
     MODULE PROCEDURE FOO2
   END INTERFACE
CONTAINS
   SUBROUTINE FOO2(R)
     REAL, INTENT(IN) :: R
     WRITE(*,*) 'REAL'
   END SUBROUTINE FOO2
END MODULE M2

PROGRAM P
   USE M1
   USE M2
   implicit none
   external bar
   CALL FOO(10)
   CALL FOO(10.)
   CALL BAR(foo) ! <<<< error needs specific interface
END PROGRAM P

The fun starts if the generic interface FOO has the same name as the specific
interfaces in each of the modules. Most compilers allow now this code although
it is ambiguous: Which of the two specific functions has to be used as actual
argument?

g95 and Portland reject the program as soon as any "foo" is used; the real
ambiguity is, however, only the FOO in "call BAR". Though probably any usage of
FOO should be rejected. (We need to check this carefully.)

Example, rejected by g95 and Portland, accepted by gfortran, NAG f95 etc.:

MODULE M1
   INTERFACE FOO
     MODULE PROCEDURE FOO
   END INTERFACE
CONTAINS
   SUBROUTINE FOO(I)
     INTEGER, INTENT(IN) :: I
     WRITE(*,*) 'INTEGER'
   END SUBROUTINE FOO
END MODULE M1

MODULE M2
   INTERFACE FOO
     MODULE PROCEDURE FOO
   END INTERFACE
CONTAINS
   SUBROUTINE FOO(R)
     REAL, INTENT(IN) :: R
     WRITE(*,*) 'REAL'
   END SUBROUTINE FOO
END MODULE M2

PROGRAM P
   USE M1
   USE M2
   implicit none
   external bar
   CALL FOO(10)
   CALL FOO(10.)
   CALL BAR(foo)
END PROGRAM P


-- 
           Summary: gfortran does not detect ambigious specific names if
                    they are the same as generic names
           Product: gcc
           Version: 4.3.0
            Status: UNCONFIRMED
          Keywords: accepts-invalid
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: burnus at gcc dot gnu dot org


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=33542


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

* [Bug fortran/33542] gfortran does not detect ambigious specific names if they are the same as generic names
  2007-09-24  9:06 [Bug fortran/33542] New: gfortran does not detect ambigious specific names if they are the same as generic names burnus at gcc dot gnu dot org
@ 2007-09-24 20:55 ` burnus at gcc dot gnu dot org
  2007-09-30 16:53 ` pault at gcc dot gnu dot org
                   ` (8 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: burnus at gcc dot gnu dot org @ 2007-09-24 20:55 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from burnus at gcc dot gnu dot org  2007-09-24 20:55 -------
Re-reading the Fortran standard, I believe now that already "call foo(10)" is
invalid (although it is not ambiguous).

"Two or more accessible entities, other than generic interfaces or
defined operators, may have the same identifier only if the identifier
is not used to refer to an entity in the scoping unit." (Fortran 2003,
"11.2.1 The USE statement and use association")

Thus, unless one claims that using "call foo(10)" refers only to the generic
interface FOO and not to the specific subroutine FOO (i.e. the identifier FOO
and FOO can be distinguished), already the "call foo(10)" is invalid.


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=33542


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

* [Bug fortran/33542] gfortran does not detect ambigious specific names if they are the same as generic names
  2007-09-24  9:06 [Bug fortran/33542] New: gfortran does not detect ambigious specific names if they are the same as generic names burnus at gcc dot gnu dot org
  2007-09-24 20:55 ` [Bug fortran/33542] " burnus at gcc dot gnu dot org
@ 2007-09-30 16:53 ` pault at gcc dot gnu dot org
  2007-10-02 10:05 ` dominiq at lps dot ens dot fr
                   ` (7 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-09-30 16:53 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from pault at gcc dot gnu dot org  2007-09-30 16:53 -------
(In reply to comment #1)
> Re-reading the Fortran standard, I believe now that already "call foo(10)" is
> invalid (although it is not ambiguous).

In fact, I believe that the ambiguity in the interface is an error; this one
liner fixes the PR -

Index: /svn/trunk/gcc/fortran/interface.c
===================================================================
*** /svn/trunk/gcc/fortran/interface.c  (revision 128873)
--- /svn/trunk/gcc/fortran/interface.c  (working copy)
*************** check_interface1 (gfc_interface *p, gfc_
*** 1044,1050 ****
        if (p->sym->name == q->sym->name && p->sym->module == q->sym->module)
          continue;

!       if (compare_interfaces (p->sym, q->sym, generic_flag))
          {
            if (referenced)
              {
--- 1044,1051 ----
        if (p->sym->name == q->sym->name && p->sym->module == q->sym->module)
          continue;

!       if (compare_interfaces (p->sym, q->sym, generic_flag)
!             || p->sym->name == q->sym->name)
          {
            if (referenced)
              {

It's just now regtesting.

Paul


-- 

pault at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
         AssignedTo|unassigned at gcc dot gnu   |pault at gcc dot gnu dot org
                   |dot org                     |
             Status|UNCONFIRMED                 |ASSIGNED
     Ever Confirmed|0                           |1
   Last reconfirmed|0000-00-00 00:00:00         |2007-09-30 16:53:34
               date|                            |


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=33542


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

* [Bug fortran/33542] gfortran does not detect ambigious specific names if they are the same as generic names
  2007-09-24  9:06 [Bug fortran/33542] New: gfortran does not detect ambigious specific names if they are the same as generic names burnus at gcc dot gnu dot org
  2007-09-24 20:55 ` [Bug fortran/33542] " burnus at gcc dot gnu dot org
  2007-09-30 16:53 ` pault at gcc dot gnu dot org
@ 2007-10-02 10:05 ` dominiq at lps dot ens dot fr
  2007-10-02 11:45 ` pault at gcc dot gnu dot org
                   ` (6 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: dominiq at lps dot ens dot fr @ 2007-10-02 10:05 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from dominiq at lps dot ens dot fr  2007-10-02 10:05 -------
Works as advertised without regression on PPC Darwin.
However there may be room for improvements for the error message:

pr33542.f90:24.9:

   USE M1
        1
Error: Ambiguous interfaces 'foo2' and 'foo2' in generic interface 'foo' at (1)

and

pr33542_1.f90:24.9:

   USE M1
        1
Error: Ambiguous interfaces 'foo' and 'foo' in generic interface 'foo' at (1)

g95 gives no such error for the first case and

In file pr33542_1.f90:28

   CALL FOO(10)
           1
Error: Name 'foo' at (1) is an ambiguous reference to 'foo' from module 'm1'
In file pr33542_1.f90:29

   CALL FOO(10.)
           1
Error: Name 'foo' at (1) is an ambiguous reference to 'foo' from module 'm1'
In file pr33542_1.f90:30

   CALL BAR(foo)
               1
Error: Symbol 'foo' at (1) is defined in multiple modules

for the second, though I don't really understand the ambiguity!-(is this
because the interfaces appear in different modules?)

Note that gcc version 4.0.3 (g95 0.91!) Jul 26 2007 rejects the first case, but
not gcc version 4.0.3 (g95 0.91!) Sep 25 2007, and xlf complains only about
"Generic procedure names are not permitted as actual arguments." for the first
case.


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=33542


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

* [Bug fortran/33542] gfortran does not detect ambigious specific names if they are the same as generic names
  2007-09-24  9:06 [Bug fortran/33542] New: gfortran does not detect ambigious specific names if they are the same as generic names burnus at gcc dot gnu dot org
                   ` (2 preceding siblings ...)
  2007-10-02 10:05 ` dominiq at lps dot ens dot fr
@ 2007-10-02 11:45 ` pault at gcc dot gnu dot org
  2007-10-02 11:47 ` pault at gcc dot gnu dot org
                   ` (5 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-10-02 11:45 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from pault at gcc dot gnu dot org  2007-10-02 11:45 -------
Subject: Bug 33542

Author: pault
Date: Tue Oct  2 11:45:11 2007
New Revision: 128954

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=128954
Log:
2007-10-02  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/33542
        * interface.c (check_interface1): Specific procedures are
        always ambiguous if they have the same name.

2007-10-02  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/33542
        * gfortran.dg/ambiguous_specific_1.f90: New test.


Added:
    trunk/gcc/testsuite/gfortran.dg/ambiguous_specific_1.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/interface.c
    trunk/gcc/testsuite/ChangeLog


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=33542


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

* [Bug fortran/33542] gfortran does not detect ambigious specific names if they are the same as generic names
  2007-09-24  9:06 [Bug fortran/33542] New: gfortran does not detect ambigious specific names if they are the same as generic names burnus at gcc dot gnu dot org
                   ` (3 preceding siblings ...)
  2007-10-02 11:45 ` pault at gcc dot gnu dot org
@ 2007-10-02 11:47 ` pault at gcc dot gnu dot org
  2007-10-04  4:46 ` pault at gcc dot gnu dot org
                   ` (4 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-10-02 11:47 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from pault at gcc dot gnu dot org  2007-10-02 11:47 -------
Fixed on trunk under 'obvious' rule.

Paul


-- 

pault at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|ASSIGNED                    |RESOLVED
         Resolution|                            |FIXED


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=33542


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

* [Bug fortran/33542] gfortran does not detect ambigious specific names if they are the same as generic names
  2007-09-24  9:06 [Bug fortran/33542] New: gfortran does not detect ambigious specific names if they are the same as generic names burnus at gcc dot gnu dot org
                   ` (4 preceding siblings ...)
  2007-10-02 11:47 ` pault at gcc dot gnu dot org
@ 2007-10-04  4:46 ` pault at gcc dot gnu dot org
  2007-10-04  4:49 ` pault at gcc dot gnu dot org
                   ` (3 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-10-04  4:46 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from pault at gcc dot gnu dot org  2007-10-04 04:45 -------
Subject: Bug 33542

Author: pault
Date: Thu Oct  4 04:45:41 2007
New Revision: 129000

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=129000
Log:
2007-10-04  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/33542
        * interface.c (check_interface1): Revert patch of 2007-10-02.

2007-10-04  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/33542
        * gfortran.dg/ambiguous_specific_1.f90: Remove.


Removed:
    trunk/gcc/testsuite/gfortran.dg/ambiguous_specific_1.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/interface.c
    trunk/gcc/testsuite/ChangeLog


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=33542


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

* [Bug fortran/33542] gfortran does not detect ambigious specific names if they are the same as generic names
  2007-09-24  9:06 [Bug fortran/33542] New: gfortran does not detect ambigious specific names if they are the same as generic names burnus at gcc dot gnu dot org
                   ` (5 preceding siblings ...)
  2007-10-04  4:46 ` pault at gcc dot gnu dot org
@ 2007-10-04  4:49 ` pault at gcc dot gnu dot org
  2007-10-07 19:05 ` patchapp at dberlin dot org
                   ` (2 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-10-04  4:49 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #7 from pault at gcc dot gnu dot org  2007-10-04 04:49 -------
Reverted because of PR33646

Paul


-- 

pault at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|RESOLVED                    |REOPENED
         Resolution|FIXED                       |


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=33542


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

* [Bug fortran/33542] gfortran does not detect ambigious specific names if they are the same as generic names
  2007-09-24  9:06 [Bug fortran/33542] New: gfortran does not detect ambigious specific names if they are the same as generic names burnus at gcc dot gnu dot org
                   ` (6 preceding siblings ...)
  2007-10-04  4:49 ` pault at gcc dot gnu dot org
@ 2007-10-07 19:05 ` patchapp at dberlin dot org
  2007-10-12 16:52 ` pault at gcc dot gnu dot org
  2007-10-14 19:27 ` pault at gcc dot gnu dot org
  9 siblings, 0 replies; 11+ messages in thread
From: patchapp at dberlin dot org @ 2007-10-07 19:05 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #8 from patchapp at dberlin dot org  2007-10-07 19:05 -------
Subject: Bug number PR33542

A patch for this bug has been added to the patch tracker.
The mailing list url for the patch is
http://gcc.gnu.org/ml/gcc-patches/2007-10/msg00372.html


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=33542


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

* [Bug fortran/33542] gfortran does not detect ambigious specific names if they are the same as generic names
  2007-09-24  9:06 [Bug fortran/33542] New: gfortran does not detect ambigious specific names if they are the same as generic names burnus at gcc dot gnu dot org
                   ` (7 preceding siblings ...)
  2007-10-07 19:05 ` patchapp at dberlin dot org
@ 2007-10-12 16:52 ` pault at gcc dot gnu dot org
  2007-10-14 19:27 ` pault at gcc dot gnu dot org
  9 siblings, 0 replies; 11+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-10-12 16:52 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #9 from pault at gcc dot gnu dot org  2007-10-12 16:52 -------
Subject: Bug 33542

Author: pault
Date: Fri Oct 12 16:51:53 2007
New Revision: 129268

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=129268
Log:
2007-10-12  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/33542
        * resolve.c (resolve_actual_arglist): If the actual argument is
        ambiguous, then there is an error.

2007-10-12  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/33542
        * gfortran.dg/ambiguous_specific_1.f90: New test.


Added:
    trunk/gcc/testsuite/gfortran.dg/ambiguous_specific_1.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/resolve.c
    trunk/gcc/testsuite/ChangeLog


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=33542


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

* [Bug fortran/33542] gfortran does not detect ambigious specific names if they are the same as generic names
  2007-09-24  9:06 [Bug fortran/33542] New: gfortran does not detect ambigious specific names if they are the same as generic names burnus at gcc dot gnu dot org
                   ` (8 preceding siblings ...)
  2007-10-12 16:52 ` pault at gcc dot gnu dot org
@ 2007-10-14 19:27 ` pault at gcc dot gnu dot org
  9 siblings, 0 replies; 11+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-10-14 19:27 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #10 from pault at gcc dot gnu dot org  2007-10-14 19:26 -------
Fixed on trunk

Paul


-- 

pault at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|REOPENED                    |RESOLVED
         Resolution|                            |FIXED


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=33542


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

end of thread, other threads:[~2007-10-14 19:27 UTC | newest]

Thread overview: 11+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2007-09-24  9:06 [Bug fortran/33542] New: gfortran does not detect ambigious specific names if they are the same as generic names burnus at gcc dot gnu dot org
2007-09-24 20:55 ` [Bug fortran/33542] " burnus at gcc dot gnu dot org
2007-09-30 16:53 ` pault at gcc dot gnu dot org
2007-10-02 10:05 ` dominiq at lps dot ens dot fr
2007-10-02 11:45 ` pault at gcc dot gnu dot org
2007-10-02 11:47 ` pault at gcc dot gnu dot org
2007-10-04  4:46 ` pault at gcc dot gnu dot org
2007-10-04  4:49 ` pault at gcc dot gnu dot org
2007-10-07 19:05 ` patchapp at dberlin dot org
2007-10-12 16:52 ` pault at gcc dot gnu dot org
2007-10-14 19:27 ` pault at gcc dot gnu dot 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).