public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/39688]  New: IMPORT of derived type fails
@ 2009-04-08 12:47 burnus at gcc dot gnu dot org
  2009-04-24 17:59 ` [Bug fortran/39688] " janus at gcc dot gnu dot org
                   ` (3 more replies)
  0 siblings, 4 replies; 5+ messages in thread
From: burnus at gcc dot gnu dot org @ 2009-04-08 12:47 UTC (permalink / raw)
  To: gcc-bugs

Reported by Bob Corbett of SUN to the J3 mailing list (who was initially not
fully convinced that the code is valid). The following program is regarded as
valid but it fails with sunf95 and gfortran (4.3/4.4/4.5, no IMPORT exists in
4.2) to compile. (It works with NAG f95, ifort, g95, xlf90.) gfortran's error
message is:

             TYPE(T3) X
                       1
Error: the type of 'x' at (1) has not been declared within the interface


"The problem, of course, is the definition of the derived
 type T2 following the interface block.  Section 12.3.2.1
 of the Fortran 2003 standard says regarding the IMPORT
 statement

      If an entity that is made accessible by this means
      is accessed by host association and is defined in
      the host scoping unit, it shall be explicitly
      declared prior to the interface body.

 That clearly requires T1 and T3 to be defined prior to the
 interface body, but it does not require T2 to be defined
 prior to the interface body.  Therefore, the program appears
 to be standard conforming."


       MODULE MOD
         TYPE T1
           SEQUENCE
           TYPE(T2), POINTER :: P
         END TYPE
         TYPE T2
           SEQUENCE
           INTEGER I
         END TYPE
       END

       PROGRAM MAIN
         USE MOD, T3 => T1, T4 => T2
         TYPE T1
           SEQUENCE
           TYPE(T2), POINTER :: P
         END TYPE
         INTERFACE SUBR
           SUBROUTINE SUBR1(X)
             IMPORT T3
             TYPE(T3) X
           END SUBROUTINE
           SUBROUTINE SUBR2(X)
             IMPORT T1
             TYPE(T1) X
           END SUBROUTINE
         END INTERFACE
         TYPE T2
           SEQUENCE
           REAL X
         END TYPE
       END

       SUBROUTINE SUBR1(X)
         USE MOD
         TYPE(T1) X
       END

       SUBROUTINE SUBR2(X)
         TYPE T1
           SEQUENCE
           TYPE(T2), POINTER :: P
         END TYPE
         TYPE T2
           SEQUENCE
           REAL X
         END TYPE
         TYPE(T1) X
       END


-- 
           Summary: IMPORT of derived type fails
           Product: gcc
           Version: 4.4.0
            Status: UNCONFIRMED
          Keywords: rejects-valid
          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=39688


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

* [Bug fortran/39688] IMPORT of derived type fails
  2009-04-08 12:47 [Bug fortran/39688] New: IMPORT of derived type fails burnus at gcc dot gnu dot org
@ 2009-04-24 17:59 ` janus at gcc dot gnu dot org
  2009-04-24 19:20 ` janus at gcc dot gnu dot org
                   ` (2 subsequent siblings)
  3 siblings, 0 replies; 5+ messages in thread
From: janus at gcc dot gnu dot org @ 2009-04-24 17:59 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from janus at gcc dot gnu dot org  2009-04-24 17:59 -------
Confirmed. Here is a reduced test case, which does not have the problem with T2
discussed in comment #0, but still fails with the same error message:

MODULE MOD
  TYPE T1
    TYPE(T1), POINTER :: P
  END TYPE
END

PROGRAM MAIN
  USE MOD, T3 => T1
  INTERFACE SUBR
    SUBROUTINE SUBR1(X)
      IMPORT T3
      TYPE(T3) X
    END SUBROUTINE
  END INTERFACE
END

The error only appears if the imported type is renamed in the USE statement.


-- 

janus at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
     Ever Confirmed|0                           |1
   Last reconfirmed|0000-00-00 00:00:00         |2009-04-24 17:59:23
               date|                            |


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


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

* [Bug fortran/39688] IMPORT of derived type fails
  2009-04-08 12:47 [Bug fortran/39688] New: IMPORT of derived type fails burnus at gcc dot gnu dot org
  2009-04-24 17:59 ` [Bug fortran/39688] " janus at gcc dot gnu dot org
@ 2009-04-24 19:20 ` janus at gcc dot gnu dot org
  2009-04-25  8:12 ` janus at gcc dot gnu dot org
  2009-04-25  8:14 ` janus at gcc dot gnu dot org
  3 siblings, 0 replies; 5+ messages in thread
From: janus at gcc dot gnu dot org @ 2009-04-24 19:20 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from janus at gcc dot gnu dot org  2009-04-24 19:20 -------
Mine. The fix is completely trivial:

Index: gcc/fortran/decl.c
===================================================================
--- gcc/fortran/decl.c  (Revision 146676)
+++ gcc/fortran/decl.c  (Arbeitskopie)
@@ -2741,7 +2741,7 @@
              goto next_item;
            }

-         st = gfc_new_symtree (&gfc_current_ns->sym_root, name);
+         st = gfc_new_symtree (&gfc_current_ns->sym_root, sym->name);
          st->n.sym = sym;
          sym->refs++;
          sym->attr.imported = 1;


-- 

janus at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
         AssignedTo|unassigned at gcc dot gnu   |janus at gcc dot gnu dot org
                   |dot org                     |
             Status|NEW                         |ASSIGNED
   Last reconfirmed|2009-04-24 17:59:23         |2009-04-24 19:20:15
               date|                            |


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


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

* [Bug fortran/39688] IMPORT of derived type fails
  2009-04-08 12:47 [Bug fortran/39688] New: IMPORT of derived type fails burnus at gcc dot gnu dot org
  2009-04-24 17:59 ` [Bug fortran/39688] " janus at gcc dot gnu dot org
  2009-04-24 19:20 ` janus at gcc dot gnu dot org
@ 2009-04-25  8:12 ` janus at gcc dot gnu dot org
  2009-04-25  8:14 ` janus at gcc dot gnu dot org
  3 siblings, 0 replies; 5+ messages in thread
From: janus at gcc dot gnu dot org @ 2009-04-25  8:12 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from janus at gcc dot gnu dot org  2009-04-25 08:12 -------
Subject: Bug 39688

Author: janus
Date: Sat Apr 25 08:11:48 2009
New Revision: 146762

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=146762
Log:
2009-04-25  Janus Weil  <janus@gcc.gnu.org>

        PR fortran/39688
        * decl.c (gfc_match_import): Use 'sym->name' instead of 'name'.
        They differ if the symbol has been use-renamed.


2009-04-25  Janus Weil  <janus@gcc.gnu.org>

        PR fortran/39688
        * gfortran.dg/import7.f90: New.


Added:
    trunk/gcc/testsuite/gfortran.dg/import7.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/decl.c
    trunk/gcc/testsuite/ChangeLog


-- 


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


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

* [Bug fortran/39688] IMPORT of derived type fails
  2009-04-08 12:47 [Bug fortran/39688] New: IMPORT of derived type fails burnus at gcc dot gnu dot org
                   ` (2 preceding siblings ...)
  2009-04-25  8:12 ` janus at gcc dot gnu dot org
@ 2009-04-25  8:14 ` janus at gcc dot gnu dot org
  3 siblings, 0 replies; 5+ messages in thread
From: janus at gcc dot gnu dot org @ 2009-04-25  8:14 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from janus at gcc dot gnu dot org  2009-04-25 08:13 -------
Fixed in r146762. Closing.


-- 

janus at gcc dot gnu dot org changed:

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


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


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

end of thread, other threads:[~2009-04-25  8:14 UTC | newest]

Thread overview: 5+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2009-04-08 12:47 [Bug fortran/39688] New: IMPORT of derived type fails burnus at gcc dot gnu dot org
2009-04-24 17:59 ` [Bug fortran/39688] " janus at gcc dot gnu dot org
2009-04-24 19:20 ` janus at gcc dot gnu dot org
2009-04-25  8:12 ` janus at gcc dot gnu dot org
2009-04-25  8:14 ` janus 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).