public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/53537] New: Abstract interface with import interferes with only-clause
@ 2012-05-31 11:03 arjen.markus at deltares dot nl
  2012-05-31 15:20 ` [Bug fortran/53537] [4.5/4.6/4.7/4.8 Regression] Explicit IMPORT of renamed USE-associated symbol fails burnus at gcc dot gnu.org
                   ` (13 more replies)
  0 siblings, 14 replies; 15+ messages in thread
From: arjen.markus at deltares dot nl @ 2012-05-31 11:03 UTC (permalink / raw)
  To: gcc-bugs

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

             Bug #: 53537
           Summary: Abstract interface with import interferes with
                    only-clause
    Classification: Unclassified
           Product: gcc
           Version: 4.6.1
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned@gcc.gnu.org
        ReportedBy: arjen.markus@deltares.nl


The program below gives errors on the use of the parameter wp. If the interface
is not present, the program gets compiled. It is probably possible 
to reduce it even further, but the error disappears when the "only: wp => dp" 
clause is commented out.

----

module select_precision
    implicit none

    integer, parameter :: sp = kind( 1.0 )
    integer, parameter :: dp = kind( 1.0d0 )

    integer, parameter :: wp = sp

end module select_precision

module ode_types
    use select_precision, only: wp => dp
    implicit none

    private
    public :: wp

    type, abstract, public :: ode_system_t
        real(wp), dimension(:), allocatable :: x, x1, x2, x3, x4
        real(wp)                            :: time, deltt
        integer                             :: size = 0
    end type ode_system_t

    interface
        function ode_derivative( this, x, time ) result(deriv)
            import                 :: ode_system_t, wp
            class(ode_system_t)    :: this
            real(wp), dimension(:) :: x
            real(wp)               :: time
            real(wp), dimension(size(x)) :: deriv
        end function ode_derivative
    end interface
end module ode_types


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

* [Bug fortran/53537] [4.5/4.6/4.7/4.8 Regression] Explicit IMPORT of renamed USE-associated symbol fails
  2012-05-31 11:03 [Bug fortran/53537] New: Abstract interface with import interferes with only-clause arjen.markus at deltares dot nl
@ 2012-05-31 15:20 ` burnus at gcc dot gnu.org
  2012-05-31 15:50 ` burnus at gcc dot gnu.org
                   ` (12 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-05-31 15:20 UTC (permalink / raw)
  To: gcc-bugs

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

Tobias Burnus <burnus at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
   Last reconfirmed|                            |2012-05-31
                 CC|                            |burnus at gcc dot gnu.org
   Target Milestone|---                         |4.5.4
            Summary|Abstract interface with     |[4.5/4.6/4.7/4.8
                   |import interferes with      |Regression] Explicit IMPORT
                   |only-clause                 |of renamed USE-associated
                   |                            |symbol fails
     Ever Confirmed|0                           |1

--- Comment #1 from Tobias Burnus <burnus at gcc dot gnu.org> 2012-05-31 15:11:32 UTC ---
Confirmed. The ingredients are:
- The use associated symbol is renamed
- IMPORT explicitly lists the renamed symbol

The following program compiles with GCC 4.3 and 4.4 but not with
4.5/4.6/4.7/4.8:

Error: Parameter 'wp' at (1) has not been declared or is a variable, which does
not reduce to a constant expression


At the "IMPORT :: wp" line (gfc_match_import), the "wp" is found and gets
imported as st->name == "dp", st->n.sym->name == "dp". In check_init_expr,
e->symtree->n.sym is a FL_VARIABLE with name "wp".



module select_precision
    integer, parameter :: dp = kind(1.0)
end module select_precision

module ode_types
    use select_precision, only: wp => dp
    implicit none
    interface
        subroutine ode_derivative(x)
            import   :: wp
            real(wp) :: x
        end subroutine ode_derivative
    end interface
end module ode_types


Draft patch (lightly tested):

--- a/gcc/fortran/decl.c
+++ b/gcc/fortran/decl.c
@@ -3188 +3188 @@ gfc_match_import (void)
-         if (gfc_find_symtree (gfc_current_ns->sym_root,name))
+         if (gfc_find_symtree (gfc_current_ns->sym_root, name))
@@ -3195 +3195 @@ gfc_match_import (void)
-         st = gfc_new_symtree (&gfc_current_ns->sym_root, sym->name);
+         st = gfc_new_symtree (&gfc_current_ns->sym_root, name);


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

* [Bug fortran/53537] [4.5/4.6/4.7/4.8 Regression] Explicit IMPORT of renamed USE-associated symbol fails
  2012-05-31 11:03 [Bug fortran/53537] New: Abstract interface with import interferes with only-clause arjen.markus at deltares dot nl
  2012-05-31 15:20 ` [Bug fortran/53537] [4.5/4.6/4.7/4.8 Regression] Explicit IMPORT of renamed USE-associated symbol fails burnus at gcc dot gnu.org
@ 2012-05-31 15:50 ` burnus at gcc dot gnu.org
  2012-05-31 16:44 ` burnus at gcc dot gnu.org
                   ` (11 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-05-31 15:50 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #2 from Tobias Burnus <burnus at gcc dot gnu.org> 2012-05-31 15:22:37 UTC ---
Side effect of that patch: In error messages, the original instead of the
renamed symbol name appears. That's independent of this PR and due to the way
USE handles renames. I have now filled PR 53542.


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

* [Bug fortran/53537] [4.5/4.6/4.7/4.8 Regression] Explicit IMPORT of renamed USE-associated symbol fails
  2012-05-31 11:03 [Bug fortran/53537] New: Abstract interface with import interferes with only-clause arjen.markus at deltares dot nl
  2012-05-31 15:20 ` [Bug fortran/53537] [4.5/4.6/4.7/4.8 Regression] Explicit IMPORT of renamed USE-associated symbol fails burnus at gcc dot gnu.org
  2012-05-31 15:50 ` burnus at gcc dot gnu.org
@ 2012-05-31 16:44 ` burnus at gcc dot gnu.org
  2012-06-01  8:04 ` burnus at gcc dot gnu.org
                   ` (10 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-05-31 16:44 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #3 from Tobias Burnus <burnus at gcc dot gnu.org> 2012-05-31 16:30:53 UTC ---
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 following patch - on top of the one in comment 1 - does *not* help:

--- a/gcc/fortran/decl.c
+++ b/gcc/fortran/decl.c
@@ -3206,3 +3206,3 @@ gfc_match_import (void)
                        gfc_get_string ("%c%s",
-                               (char) TOUPPER ((unsigned char) sym->name[0]),
+                               (char) TOUPPER ((unsigned char) name[0]),
                                &sym->name[1]));


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

* [Bug fortran/53537] [4.5/4.6/4.7/4.8 Regression] Explicit IMPORT of renamed USE-associated symbol fails
  2012-05-31 11:03 [Bug fortran/53537] New: Abstract interface with import interferes with only-clause arjen.markus at deltares dot nl
                   ` (2 preceding siblings ...)
  2012-05-31 16:44 ` burnus at gcc dot gnu.org
@ 2012-06-01  8:04 ` burnus at gcc dot gnu.org
  2012-06-13 13:54 ` rguenth at gcc dot gnu.org
                   ` (9 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-06-01  8:04 UTC (permalink / raw)
  To: gcc-bugs

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.


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

* [Bug fortran/53537] [4.5/4.6/4.7/4.8 Regression] Explicit IMPORT of renamed USE-associated symbol fails
  2012-05-31 11:03 [Bug fortran/53537] New: Abstract interface with import interferes with only-clause arjen.markus at deltares dot nl
                   ` (3 preceding siblings ...)
  2012-06-01  8:04 ` burnus at gcc dot gnu.org
@ 2012-06-13 13:54 ` rguenth at gcc dot gnu.org
  2012-07-02 12:58 ` [Bug fortran/53537] [4.6/4.7/4.8 " rguenth at gcc dot gnu.org
                   ` (8 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: rguenth at gcc dot gnu.org @ 2012-06-13 13:54 UTC (permalink / raw)
  To: gcc-bugs

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

Richard Guenther <rguenth at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Priority|P3                          |P4


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

* [Bug fortran/53537] [4.6/4.7/4.8 Regression] Explicit IMPORT of renamed USE-associated symbol fails
  2012-05-31 11:03 [Bug fortran/53537] New: Abstract interface with import interferes with only-clause arjen.markus at deltares dot nl
                   ` (4 preceding siblings ...)
  2012-06-13 13:54 ` rguenth at gcc dot gnu.org
@ 2012-07-02 12:58 ` rguenth at gcc dot gnu.org
  2013-01-09 13:54 ` mikael at gcc dot gnu.org
                   ` (7 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: rguenth at gcc dot gnu.org @ 2012-07-02 12:58 UTC (permalink / raw)
  To: gcc-bugs

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

Richard Guenther <rguenth at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
   Target Milestone|4.5.4                       |4.6.4


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

* [Bug fortran/53537] [4.6/4.7/4.8 Regression] Explicit IMPORT of renamed USE-associated symbol fails
  2012-05-31 11:03 [Bug fortran/53537] New: Abstract interface with import interferes with only-clause arjen.markus at deltares dot nl
                   ` (5 preceding siblings ...)
  2012-07-02 12:58 ` [Bug fortran/53537] [4.6/4.7/4.8 " rguenth at gcc dot gnu.org
@ 2013-01-09 13:54 ` mikael at gcc dot gnu.org
  2013-01-15 17:50 ` mikael at gcc dot gnu.org
                   ` (6 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: mikael at gcc dot gnu.org @ 2013-01-09 13:54 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #5 from Mikael Morin <mikael at gcc dot gnu.org> 2013-01-09 13:54:15 UTC ---
Created attachment 29124
  --> http://gcc.gnu.org/bugzilla/attachment.cgi?id=29124
"Fix" for the regression in comment #3

For the remaining problem:

(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

maybe we can just remove the error. After all, there is already
non-interface-specific code to diagnose uses of undeclared types.
For that code to trigger in place of the error above, a few adjustments are
needed to avoid searching the type outside the interface (so that the type is
really not found).

With the attached patch, comment #0, comment #1 and comment #4 are accepted,
but a few adjustments are needed in the testsuite:
from:

        type(fcnparms) :: fparams ! { dg-error "not been declared within the in
                                 1
Error: The type of 'fparams' at (1) has not been declared within the interface

to:

        type(fcnparms) :: fparams ! { dg-error "not been declared within the in
                      1
Error: Derived type 'fcnparms' at (1) is being used before it is defined


I will test the patch against the full testsuite.  As it touches the core of
the symbol resolution, it's quite to be expected that it has "interesting" side
effects.


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

* [Bug fortran/53537] [4.6/4.7/4.8 Regression] Explicit IMPORT of renamed USE-associated symbol fails
  2012-05-31 11:03 [Bug fortran/53537] New: Abstract interface with import interferes with only-clause arjen.markus at deltares dot nl
                   ` (6 preceding siblings ...)
  2013-01-09 13:54 ` mikael at gcc dot gnu.org
@ 2013-01-15 17:50 ` mikael at gcc dot gnu.org
  2013-01-28 14:37 ` mikael at gcc dot gnu.org
                   ` (5 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: mikael at gcc dot gnu.org @ 2013-01-15 17:50 UTC (permalink / raw)
  To: gcc-bugs


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

Mikael Morin <mikael at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |mikael at gcc dot gnu.org

--- Comment #6 from Mikael Morin <mikael at gcc dot gnu.org> 2013-01-15 17:49:45 UTC ---
Patch submitted:
http://gcc.gnu.org/ml/gcc-patches/2013-01/msg00545.html


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

* [Bug fortran/53537] [4.6/4.7/4.8 Regression] Explicit IMPORT of renamed USE-associated symbol fails
  2012-05-31 11:03 [Bug fortran/53537] New: Abstract interface with import interferes with only-clause arjen.markus at deltares dot nl
                   ` (7 preceding siblings ...)
  2013-01-15 17:50 ` mikael at gcc dot gnu.org
@ 2013-01-28 14:37 ` mikael at gcc dot gnu.org
  2013-01-28 20:09 ` dominiq at lps dot ens.fr
                   ` (4 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: mikael at gcc dot gnu.org @ 2013-01-28 14:37 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #7 from Mikael Morin <mikael at gcc dot gnu.org> 2013-01-28 14:37:26 UTC ---
Author: mikael
Date: Mon Jan 28 14:37:20 2013
New Revision: 195506

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=195506
Log:
2013-01-28  Tobias Burnus  <burnus@net-b.de>
        Mikael Morin  <mikael@gcc.gnu.org>

    PR fortran/53537
    * symbol.c (gfc_find_sym_tree): Don't look for the symbol outside an
    interface block.
    (gfc_get_ha_symtree): Let gfc_find_sym_tree lookup the parent namespace.
    * decl.c (gfc_match_data_decl): Ditto.
    (variable_decl): Remove undeclared type error.
    (gfc_match_import): Use renamed instead of original name.

2013-01-28  Tobias Burnus  <burnus@net-b.de>
        Mikael Morin  <mikael@gcc.gnu.org>

    PR fortran/53537
    * gfortran.dg/import2.f90: Adjust undeclared type error messages.
    * gfortran.dg/import8.f90: Likewise.
    * gfortran.dg/interface_derived_type_1.f90: Likewise.
    * gfortran.dg/import10.f90: New test.
    * gfortran.dg/import11.f90: Likewise


Added:
    trunk/gcc/testsuite/gfortran.dg/import10.f90
    trunk/gcc/testsuite/gfortran.dg/import11.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/decl.c
    trunk/gcc/fortran/symbol.c
    trunk/gcc/testsuite/ChangeLog
    trunk/gcc/testsuite/gfortran.dg/import2.f90
    trunk/gcc/testsuite/gfortran.dg/import8.f90
    trunk/gcc/testsuite/gfortran.dg/interface_derived_type_1.f90


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

* [Bug fortran/53537] [4.6/4.7/4.8 Regression] Explicit IMPORT of renamed USE-associated symbol fails
  2012-05-31 11:03 [Bug fortran/53537] New: Abstract interface with import interferes with only-clause arjen.markus at deltares dot nl
                   ` (8 preceding siblings ...)
  2013-01-28 14:37 ` mikael at gcc dot gnu.org
@ 2013-01-28 20:09 ` dominiq at lps dot ens.fr
  2013-01-29 12:43 ` mikael at gcc dot gnu.org
                   ` (3 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: dominiq at lps dot ens.fr @ 2013-01-28 20:09 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #8 from Dominique d'Humieres <dominiq at lps dot ens.fr> 2013-01-28 20:08:50 UTC ---
After revision 195506, the test in pr44830 compiles without error.


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

* [Bug fortran/53537] [4.6/4.7/4.8 Regression] Explicit IMPORT of renamed USE-associated symbol fails
  2012-05-31 11:03 [Bug fortran/53537] New: Abstract interface with import interferes with only-clause arjen.markus at deltares dot nl
                   ` (9 preceding siblings ...)
  2013-01-28 20:09 ` dominiq at lps dot ens.fr
@ 2013-01-29 12:43 ` mikael at gcc dot gnu.org
  2013-02-15  7:30 ` [Bug fortran/53537] [4.6/4.7 " burnus at gcc dot gnu.org
                   ` (2 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: mikael at gcc dot gnu.org @ 2013-01-29 12:43 UTC (permalink / raw)
  To: gcc-bugs


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

Mikael Morin <mikael at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |jkrahn at nc dot rr.com

--- Comment #9 from Mikael Morin <mikael at gcc dot gnu.org> 2013-01-29 12:43:13 UTC ---
*** Bug 44830 has been marked as a duplicate of this bug. ***


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

* [Bug fortran/53537] [4.6/4.7 Regression] Explicit IMPORT of renamed USE-associated symbol fails
  2012-05-31 11:03 [Bug fortran/53537] New: Abstract interface with import interferes with only-clause arjen.markus at deltares dot nl
                   ` (10 preceding siblings ...)
  2013-01-29 12:43 ` mikael at gcc dot gnu.org
@ 2013-02-15  7:30 ` burnus at gcc dot gnu.org
  2013-02-17 23:00 ` mikael at gcc dot gnu.org
  2013-02-19 13:08 ` mikael at gcc dot gnu.org
  13 siblings, 0 replies; 15+ messages in thread
From: burnus at gcc dot gnu.org @ 2013-02-15  7:30 UTC (permalink / raw)
  To: gcc-bugs


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

Tobias Burnus <burnus at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |burnus at gcc dot gnu.org
            Summary|[4.6/4.7/4.8 Regression]    |[4.6/4.7 Regression]
                   |Explicit IMPORT of renamed  |Explicit IMPORT of renamed
                   |USE-associated symbol fails |USE-associated symbol fails

--- Comment #10 from Tobias Burnus <burnus at gcc dot gnu.org> 2013-02-15 07:30:08 UTC ---
The committed patch (comment 7) seems to have fixed all testcases of this PR.

Hence, I think only backporting or closing seems to be required.


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

* [Bug fortran/53537] [4.6/4.7 Regression] Explicit IMPORT of renamed USE-associated symbol fails
  2012-05-31 11:03 [Bug fortran/53537] New: Abstract interface with import interferes with only-clause arjen.markus at deltares dot nl
                   ` (11 preceding siblings ...)
  2013-02-15  7:30 ` [Bug fortran/53537] [4.6/4.7 " burnus at gcc dot gnu.org
@ 2013-02-17 23:00 ` mikael at gcc dot gnu.org
  2013-02-19 13:08 ` mikael at gcc dot gnu.org
  13 siblings, 0 replies; 15+ messages in thread
From: mikael at gcc dot gnu.org @ 2013-02-17 23:00 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #11 from Mikael Morin <mikael at gcc dot gnu.org> 2013-02-17 22:59:59 UTC ---
Author: mikael
Date: Sun Feb 17 22:59:52 2013
New Revision: 196112

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=196112
Log:
2013-02-17  Tobias Burnus  <burnus@net-b.de>
        Mikael Morin  <mikael@gcc.gnu.org>

    Backport from trunk
    2013-01-28  Tobias Burnus  <burnus@net-b.de>
            Mikael Morin  <mikael@gcc.gnu.org>

    PR fortran/53537
    * symbol.c (gfc_find_sym_tree): Don't look for the symbol outside an
    interface block.
    (gfc_get_ha_symtree): Let gfc_find_sym_tree lookup the parent namespace.
    * decl.c (gfc_match_data_decl): Ditto.
    (variable_decl): Remove undeclared type error.
    (gfc_match_import): Use renamed instead of original name.

2013-02-17  Tobias Burnus  <burnus@net-b.de>
        Mikael Morin  <mikael@gcc.gnu.org>

    Backport from trunk
    2013-01-28  Tobias Burnus  <burnus@net-b.de>
            Mikael Morin  <mikael@gcc.gnu.org>

    PR fortran/53537
    * gfortran.dg/import2.f90: Adjust undeclared type error messages.
    * gfortran.dg/import8.f90: Likewise.
    * gfortran.dg/interface_derived_type_1.f90: Likewise.
    * gfortran.dg/import10.f90: New test.
    * gfortran.dg/import11.f90: Likewise


Added:
    branches/gcc-4_7-branch/gcc/testsuite/gfortran.dg/import10.f90
    branches/gcc-4_7-branch/gcc/testsuite/gfortran.dg/import11.f90
Modified:
    branches/gcc-4_7-branch/gcc/fortran/ChangeLog
    branches/gcc-4_7-branch/gcc/fortran/decl.c
    branches/gcc-4_7-branch/gcc/fortran/symbol.c
    branches/gcc-4_7-branch/gcc/testsuite/ChangeLog
    branches/gcc-4_7-branch/gcc/testsuite/gfortran.dg/import2.f90
    branches/gcc-4_7-branch/gcc/testsuite/gfortran.dg/import8.f90
   
branches/gcc-4_7-branch/gcc/testsuite/gfortran.dg/interface_derived_type_1.f90


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

* [Bug fortran/53537] [4.6/4.7 Regression] Explicit IMPORT of renamed USE-associated symbol fails
  2012-05-31 11:03 [Bug fortran/53537] New: Abstract interface with import interferes with only-clause arjen.markus at deltares dot nl
                   ` (12 preceding siblings ...)
  2013-02-17 23:00 ` mikael at gcc dot gnu.org
@ 2013-02-19 13:08 ` mikael at gcc dot gnu.org
  13 siblings, 0 replies; 15+ messages in thread
From: mikael at gcc dot gnu.org @ 2013-02-19 13:08 UTC (permalink / raw)
  To: gcc-bugs


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

Mikael Morin <mikael at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|NEW                         |RESOLVED
         Resolution|                            |FIXED
         AssignedTo|unassigned at gcc dot       |mikael at gcc dot gnu.org
                   |gnu.org                     |
   Target Milestone|4.6.4                       |4.7.3

--- Comment #12 from Mikael Morin <mikael at gcc dot gnu.org> 2013-02-19 13:07:40 UTC ---
The 4.6 backport gives a few regression. Namely:

FAIL: gfortran.dg/import2.f90  -O   (test for errors, line 40)
FAIL: gfortran.dg/import2.f90  -O   (test for errors, line 59)
FAIL: gfortran.dg/import2.f90  -O   (test for errors, line 65)
FAIL: gfortran.dg/import2.f90  -O   (test for errors, line 77)
FAIL: gfortran.dg/import8.f90  -O   (test for errors, line 15)
FAIL: gfortran.dg/interface_derived_type_1.f90  -O   (test for errors, line 16)


The reason is in gfc_use_derived, gfc_find_symbol returns a symbol of flavor
FL_DERIVED, so that no error is issued.  On trunk the symbol is of flavor
FL_PROCEDURE.  I don't feel like spending too much time on this, so I will just
leave 4.6 unfixed.

Thus, FIXED for 4.7.3 and 4.8.0,
WONTFIX for 4.6.*.


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

end of thread, other threads:[~2013-02-19 13:08 UTC | newest]

Thread overview: 15+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2012-05-31 11:03 [Bug fortran/53537] New: Abstract interface with import interferes with only-clause arjen.markus at deltares dot nl
2012-05-31 15:20 ` [Bug fortran/53537] [4.5/4.6/4.7/4.8 Regression] Explicit IMPORT of renamed USE-associated symbol fails burnus at gcc dot gnu.org
2012-05-31 15:50 ` burnus at gcc dot gnu.org
2012-05-31 16:44 ` burnus at gcc dot gnu.org
2012-06-01  8:04 ` burnus at gcc dot gnu.org
2012-06-13 13:54 ` rguenth at gcc dot gnu.org
2012-07-02 12:58 ` [Bug fortran/53537] [4.6/4.7/4.8 " rguenth at gcc dot gnu.org
2013-01-09 13:54 ` mikael at gcc dot gnu.org
2013-01-15 17:50 ` mikael at gcc dot gnu.org
2013-01-28 14:37 ` mikael at gcc dot gnu.org
2013-01-28 20:09 ` dominiq at lps dot ens.fr
2013-01-29 12:43 ` mikael at gcc dot gnu.org
2013-02-15  7:30 ` [Bug fortran/53537] [4.6/4.7 " burnus at gcc dot gnu.org
2013-02-17 23:00 ` mikael at gcc dot gnu.org
2013-02-19 13:08 ` mikael 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).