public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/33233]  New: Parent and contained procedure: Wrongly treated as generic procedures
@ 2007-08-29 16:02 burnus at gcc dot gnu dot org
  2007-10-03  4:13 ` [Bug fortran/33233] " pault at gcc dot gnu dot org
                   ` (5 more replies)
  0 siblings, 6 replies; 7+ messages in thread
From: burnus at gcc dot gnu dot org @ 2007-08-29 16:02 UTC (permalink / raw)
  To: gcc-bugs

This is a follow up to PR30746.

While I believe the test case in PR30746 is correct, I think the
gfortran.dg/host_assoc_function_1.f90 test case is wrong.

(Simplified, see testsuite for the full file)

MODULE m
  REAL :: x(3) = (/ 1.5, 2.5, 3.5 /)
CONTAINS
  SUBROUTINE s
    if (x(2) .ne. 2.5) call abort ()
  CONTAINS
    FUNCTION x(n, m)
      x = REAL(n)**m
    END FUNCTION
  END SUBROUTINE s
END MODULE m

I am very much in favour of the other compilers which think the "x" in "s"
refers to only the contained function "x" and not to the variable. gfortran
somehow seems to treat the symbol "x" as generic symbol which means with one
argument the variable and with two the function.
I would argue that the function name makes the variable inaccessible.

Using NAG's f95:
Error: host_assoc_function_1.f90, line 22: Too few arguments in reference to X
Error: host_assoc_function_1.f90, line 23: Too few arguments in reference to Z

ifort:
fortcom: Error: host_assoc_function_1.f90, line 22: A non-optional actual
argument must be present when invoking a procedure with an explicit interface. 
 [M] [...]


-- 
           Summary: Parent and contained procedure: Wrongly treated as
                    generic procedures
           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=33233


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

* [Bug fortran/33233] Parent and contained procedure: Wrongly treated as generic procedures
  2007-08-29 16:02 [Bug fortran/33233] New: Parent and contained procedure: Wrongly treated as generic procedures burnus at gcc dot gnu dot org
@ 2007-10-03  4:13 ` pault at gcc dot gnu dot org
  2007-10-11 14:55 ` pault at gcc dot gnu dot org
                   ` (4 subsequent siblings)
  5 siblings, 0 replies; 7+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-10-03  4:13 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from pault at gcc dot gnu dot org  2007-10-03 04:13 -------
Tobias,

I am not sure how this got so screwed up.  As you say, the Cohen testcase is
correct and I must, surely(?), have been checking that.... *sigh*

Confirmed

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-10-03 04:13:42
               date|                            |


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


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

* [Bug fortran/33233] Parent and contained procedure: Wrongly treated as generic procedures
  2007-08-29 16:02 [Bug fortran/33233] New: Parent and contained procedure: Wrongly treated as generic procedures burnus at gcc dot gnu dot org
  2007-10-03  4:13 ` [Bug fortran/33233] " pault at gcc dot gnu dot org
@ 2007-10-11 14:55 ` pault at gcc dot gnu dot org
  2007-10-11 17:31 ` dominiq at lps dot ens dot fr
                   ` (3 subsequent siblings)
  5 siblings, 0 replies; 7+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-10-11 14:55 UTC (permalink / raw)
  To: gcc-bugs

[-- Warning: decoded text below may be mangled, UTF-8 assumed --]
[-- Attachment #1: Type: text/plain, Size: 2589 bytes --]



------- Comment #2 from pault at gcc dot gnu dot org  2007-10-11 14:55 -------
(In reply to comment #1)
Ah.... this bug was present before my patch for PR30746.  I can see from my
notes that I was fixated on PR30746, whilst not altering the behaviour of
gfortran in any other way....., whether right or wrong.  Bah!

With the patch below, we get the correct behaviour for 

MODULE m
  REAL :: x(3) = (/ 1.5, 2.5, 3.5 /)
CONTAINS
  SUBROUTINE s
    if (x(2) .eq. 2.5) call abort ()
  CONTAINS
    FUNCTION x(n, m)
      integer, optional :: m
      if (present(m)) then
        x = REAL(n)**m
      else
        x = 0.0
      end if
    END FUNCTION
  END SUBROUTINE s
END MODULE m
  use m
  call s
end

Paul

Index: gcc/fortran/resolve.c
===================================================================
*** gcc/fortran/resolve.c       (révision 129121)
--- gcc/fortran/resolve.c       (copie de travail)
*************** check_host_association (gfc_expr *e)
*** 3989,3999 ****
      return retval;

    if (gfc_current_ns->parent
-       && gfc_current_ns->parent->parent
        && old_sym->ns != gfc_current_ns)
      {
!       gfc_find_symbol (old_sym->name, gfc_current_ns->parent, 1, &sym);
!       if (sym && old_sym != sym && sym->attr.flavor == FL_PROCEDURE)
        {
          temp_locus = gfc_current_locus;
          gfc_current_locus = e->where;
--- 3989,4000 ----
      return retval;

    if (gfc_current_ns->parent
        && old_sym->ns != gfc_current_ns)
      {
!       gfc_find_symbol (old_sym->name, gfc_current_ns, 1, &sym);
!       if (sym && old_sym != sym
!             && sym->attr.flavor == FL_PROCEDURE
!             && sym->attr.contained)
        {
          temp_locus = gfc_current_locus;
          gfc_current_locus = e->where;

Index: D:/svn/trunk/gcc/testsuite/gfortran.dg/host_assoc_function_1.f90
===================================================================
*** D:/svn/trunk/gcc/testsuite/gfortran.dg/host_assoc_function_1.f90   
(révisio
n 129121)
--- D:/svn/trunk/gcc/testsuite/gfortran.dg/host_assoc_function_1.f90    (copie
d
e travail)
*************** MODULE m
*** 19,26 ****
    end interface
  CONTAINS
    SUBROUTINE s
!     if (x(2) .ne. 2.5) call abort ()
!     if (z(3) .ne. real (3)**3) call abort ()
      CALL inner
    CONTAINS
      SUBROUTINE inner
--- 19,26 ----
    end interface
  CONTAINS
    SUBROUTINE s
!     if (x(2, 3) .ne. real (2)**3) call abort ()
!     if (z(3, 3) .ne. real (3)**3) call abort ()
      CALL inner
    CONTAINS
      SUBROUTINE inner


-- 


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


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

* [Bug fortran/33233] Parent and contained procedure: Wrongly treated as generic procedures
  2007-08-29 16:02 [Bug fortran/33233] New: Parent and contained procedure: Wrongly treated as generic procedures burnus at gcc dot gnu dot org
  2007-10-03  4:13 ` [Bug fortran/33233] " pault at gcc dot gnu dot org
  2007-10-11 14:55 ` pault at gcc dot gnu dot org
@ 2007-10-11 17:31 ` dominiq at lps dot ens dot fr
  2007-10-15  1:06 ` patchapp at dberlin dot org
                   ` (2 subsequent siblings)
  5 siblings, 0 replies; 7+ messages in thread
From: dominiq at lps dot ens dot fr @ 2007-10-11 17:31 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from dominiq at lps dot ens dot fr  2007-10-11 17:30 -------
Works as expected: now gfortran agrees with xlf. Regtest almost finished in 32
bit mode.


-- 


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


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

* [Bug fortran/33233] Parent and contained procedure: Wrongly treated as generic procedures
  2007-08-29 16:02 [Bug fortran/33233] New: Parent and contained procedure: Wrongly treated as generic procedures burnus at gcc dot gnu dot org
                   ` (2 preceding siblings ...)
  2007-10-11 17:31 ` dominiq at lps dot ens dot fr
@ 2007-10-15  1:06 ` patchapp at dberlin dot org
  2007-10-18 12:49 ` pault at gcc dot gnu dot org
  2007-10-18 13:54 ` pault at gcc dot gnu dot org
  5 siblings, 0 replies; 7+ messages in thread
From: patchapp at dberlin dot org @ 2007-10-15  1:06 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from patchapp at dberlin dot org  2007-10-15 01:06 -------
Subject: Bug number PR33233

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/msg00745.html


-- 


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


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

* [Bug fortran/33233] Parent and contained procedure: Wrongly treated as generic procedures
  2007-08-29 16:02 [Bug fortran/33233] New: Parent and contained procedure: Wrongly treated as generic procedures burnus at gcc dot gnu dot org
                   ` (3 preceding siblings ...)
  2007-10-15  1:06 ` patchapp at dberlin dot org
@ 2007-10-18 12:49 ` pault at gcc dot gnu dot org
  2007-10-18 13:54 ` pault at gcc dot gnu dot org
  5 siblings, 0 replies; 7+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-10-18 12:49 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from pault at gcc dot gnu dot org  2007-10-18 12:48 -------
Subject: Bug 33233

Author: pault
Date: Thu Oct 18 12:48:37 2007
New Revision: 129437

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

        PR fortran/33233
        * resolve.c (check_host_association): Check singly contained
        namespaces and start search for symbol in current namespace.

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

        PR fortran/33233
        * gfortran.dg/host_assoc_function_1.f90: Correct references.
        * gfortran.dg/host_assoc_function_3.f90: New test.

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


-- 


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


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

* [Bug fortran/33233] Parent and contained procedure: Wrongly treated as generic procedures
  2007-08-29 16:02 [Bug fortran/33233] New: Parent and contained procedure: Wrongly treated as generic procedures burnus at gcc dot gnu dot org
                   ` (4 preceding siblings ...)
  2007-10-18 12:49 ` pault at gcc dot gnu dot org
@ 2007-10-18 13:54 ` pault at gcc dot gnu dot org
  5 siblings, 0 replies; 7+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-10-18 13:54 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from pault at gcc dot gnu dot org  2007-10-18 13:54 -------
Fixed on trunk.

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=33233


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

end of thread, other threads:[~2007-10-18 13:54 UTC | newest]

Thread overview: 7+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2007-08-29 16:02 [Bug fortran/33233] New: Parent and contained procedure: Wrongly treated as generic procedures burnus at gcc dot gnu dot org
2007-10-03  4:13 ` [Bug fortran/33233] " pault at gcc dot gnu dot org
2007-10-11 14:55 ` pault at gcc dot gnu dot org
2007-10-11 17:31 ` dominiq at lps dot ens dot fr
2007-10-15  1:06 ` patchapp at dberlin dot org
2007-10-18 12:49 ` pault at gcc dot gnu dot org
2007-10-18 13:54 ` 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).