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

--- Comment #4 from Tobias Burnus <burnus at gcc dot gnu.org> 2012-06-01 
08:04:09 UTC ---
(In reply to comment #3)
> The patch of comment 1 fails for testsuite/gfortran.dg/import7.f90:
> 
>              TYPE(T3) X
>                        1
>   Error: The type of 'x' at (1) has not been declared within the interface

The problem is the check in decl.c's variable_decl:

      st = gfc_find_symtree (gfc_current_ns->sym_root,
                             current_ts.u.derived->name);

Here, "current_ts.u.derived->name" is "t1" (original name) while the symtree
has "t3" (renamed/imported name).  Thus, "st" is NULL.



However, the current code (without the patch) fails for the following program:

             type t1
                    1
  Error: Derived type definition of 't1' at (1) has already been defined

Using the patch it works.

! ----------------------
       MODULE MOD
         TYPE T1
           SEQUENCE
           integer :: j
         END TYPE t1
       END
       PROGRAM MAIN
         USE MOD, T3 => T1
         INTERFACE SUBR
           SUBROUTINE SUBR1(X,y)
             IMPORT :: T3
             type t1
!               sequence
!               integer :: i
             end type t1
             TYPE(T3) X
!             TYPE(T1) X
           END SUBROUTINE
       end program main
! ----------------------


One solution to the issue of comment 3 would be to change the gfc_find_symtree
by gfc_find_symbol; however, for the code above the gfc_find_symbol would find
two symbols: The locally defined "t1" and the imported one (with sym name "t1"
and symtree name "t3" or "t1" [w/ and w/o patch of comment 1]).

A 'simple' copy of the symbol plus changing its name might work (and fix the
issue of PR 53542, if also done in module.c); however, one also needs to ensure
that non-SEQUENCE/non-Bind(C) types are regarded as the same.

Reply via email to