public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/56500] New: [OOP] "IMPLICIT CLASS(...)" wrongly rejected
@ 2013-03-01 18:07 burnus at gcc dot gnu.org
  2013-03-02  0:07 ` [Bug fortran/56500] " burnus at gcc dot gnu.org
                   ` (10 more replies)
  0 siblings, 11 replies; 12+ messages in thread
From: burnus at gcc dot gnu.org @ 2013-03-01 18:07 UTC (permalink / raw)
  To: gcc-bugs


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

             Bug #: 56500
           Summary: [OOP] "IMPLICIT CLASS(...)" wrongly rejected
    Classification: Unclassified
           Product: gcc
           Version: 4.8.0
            Status: UNCONFIRMED
          Keywords: rejects-valid
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned@gcc.gnu.org
        ReportedBy: burnus@gcc.gnu.org
                CC: janus@gcc.gnu.org


Found at http://mailman.j3-fortran.org/pipermail/j3/2013-March/006167.html

"IMPLICIT CLASS(...) (...)" does not properly work with gfortran.


R560  implicit-stmt  is  IMPLICIT implicit-spec-list
                     or  IMPLICIT NONE
R561  implicit-spec  is  declaration-type-spec ( letter-spec-list )
R403 declaration-type-spec  is  intrinsic-type-spec
                            or  TYPE ( intrinsic-type-spec )
                            or  TYPE ( derived-type-spec )
                            or  CLASS ( derived-type-spec )
                            or  CLASS ( * )


Example by Reinhold Bader:

module mod_upimp
  type :: foo
     integer :: i
  end type
end module
program upimp
  use mod_upimp
  implicit class(foo) (a-b)
  implicit class(*) (c)
  allocatable :: aaf, caf
  allocate(aaf, source=foo(2))
  allocate(caf, source=foo(3))
  select type (aaf)
  type is (foo)
    write(*,*) aaf
  end select
  select type (caf)
  type is (foo)
    write(*,*) caf
  end select
end program


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

* [Bug fortran/56500] [OOP] "IMPLICIT CLASS(...)" wrongly rejected
  2013-03-01 18:07 [Bug fortran/56500] New: [OOP] "IMPLICIT CLASS(...)" wrongly rejected burnus at gcc dot gnu.org
@ 2013-03-02  0:07 ` burnus at gcc dot gnu.org
  2013-03-17 12:55 ` janus at gcc dot gnu.org
                   ` (9 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: burnus at gcc dot gnu.org @ 2013-03-02  0:07 UTC (permalink / raw)
  To: gcc-bugs


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

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

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

--- Comment #1 from Tobias Burnus <burnus at gcc dot gnu.org> 2013-03-02 00:06:45 UTC ---
The problem seems to be that "class_ok" is not true; the reason seems to be
that gfc_build_class_symbol does not get called.

I am not sure, when it has to be called but it currently fails for:

  implicit class(*) (a-z)
  allocatable :: foo
  end
and for
  subroutine foo(x)
  implicit class(*) (a-z)
  end

The error message is printed in resolve.c's resolve_fl_var_and_proc:

  /* Constraints on polymorphic variables.  */
...
      if (!sym->attr.class_ok && !sym->attr.use_assoc && !sym->assoc)
        {
          gfc_error ("CLASS variable '%s' at %L must be dummy, allocatable "
                     "or pointer", sym->name, &sym->declared_at);


gfc_build_class_symbol is currently only called in decl.c via "build_struct"
and via attr_decl1. One probably has to call it in symbol.c's 
gfc_set_default_type


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

* [Bug fortran/56500] [OOP] "IMPLICIT CLASS(...)" wrongly rejected
  2013-03-01 18:07 [Bug fortran/56500] New: [OOP] "IMPLICIT CLASS(...)" wrongly rejected burnus at gcc dot gnu.org
  2013-03-02  0:07 ` [Bug fortran/56500] " burnus at gcc dot gnu.org
@ 2013-03-17 12:55 ` janus at gcc dot gnu.org
  2013-03-17 13:12 ` janus at gcc dot gnu.org
                   ` (8 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: janus at gcc dot gnu.org @ 2013-03-17 12:55 UTC (permalink / raw)
  To: gcc-bugs


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

janus at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
   Last reconfirmed|                            |2013-03-17
     Ever Confirmed|0                           |1

--- Comment #2 from janus at gcc dot gnu.org 2013-03-17 12:55:07 UTC ---
The following patch makes the example in comment 0 work:


Index: gcc/fortran/decl.c
===================================================================
--- gcc/fortran/decl.c    (revision 196748)
+++ gcc/fortran/decl.c    (working copy)
@@ -6293,6 +6293,13 @@ attr_decl1 (void)
     }
     }

+  if (sym->ts.type == BT_UNKNOWN
+      && gfc_set_default_type (sym, 1, NULL) == FAILURE)
+    {
+      m = MATCH_ERROR;
+      goto cleanup;
+    }
+
   /* Update symbol table.  DIMENSION attribute is set in
      gfc_set_array_spec().  For CLASS variables, this must be applied
      to the first component, or '_data' field.  */


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

* [Bug fortran/56500] [OOP] "IMPLICIT CLASS(...)" wrongly rejected
  2013-03-01 18:07 [Bug fortran/56500] New: [OOP] "IMPLICIT CLASS(...)" wrongly rejected burnus at gcc dot gnu.org
  2013-03-02  0:07 ` [Bug fortran/56500] " burnus at gcc dot gnu.org
  2013-03-17 12:55 ` janus at gcc dot gnu.org
@ 2013-03-17 13:12 ` janus at gcc dot gnu.org
  2013-03-17 16:00 ` janus at gcc dot gnu.org
                   ` (7 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: janus at gcc dot gnu.org @ 2013-03-17 13:12 UTC (permalink / raw)
  To: gcc-bugs


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

janus at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|NEW                         |ASSIGNED

--- Comment #3 from janus at gcc dot gnu.org 2013-03-17 13:12:02 UTC ---
... and this hunk cures the error on comment 1:

Index: gcc/fortran/resolve.c
===================================================================
--- gcc/fortran/resolve.c    (revision 196748)
+++ gcc/fortran/resolve.c    (working copy)
@@ -318,7 +318,13 @@ resolve_formal_arglist (gfc_symbol *proc)
     {
       if (sym->ts.type == BT_UNKNOWN && !proc->attr.intrinsic
           && (!sym->attr.function || sym->result == sym))
-        gfc_set_default_type (sym, 1, sym->ns);
+        {
+          gfc_set_default_type (sym, 1, sym->ns);
+          if (sym->ts.type == BT_CLASS
+          && gfc_build_class_symbol (&sym->ts, &sym->attr,
+                         &sym->as, false) == FAILURE)
+        continue;
+        }
     }

       as = sym->ts.type == BT_CLASS && sym->attr.class_ok


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

* [Bug fortran/56500] [OOP] "IMPLICIT CLASS(...)" wrongly rejected
  2013-03-01 18:07 [Bug fortran/56500] New: [OOP] "IMPLICIT CLASS(...)" wrongly rejected burnus at gcc dot gnu.org
                   ` (2 preceding siblings ...)
  2013-03-17 13:12 ` janus at gcc dot gnu.org
@ 2013-03-17 16:00 ` janus at gcc dot gnu.org
  2013-03-17 19:46 ` dominiq at lps dot ens.fr
                   ` (6 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: janus at gcc dot gnu.org @ 2013-03-17 16:00 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #4 from janus at gcc dot gnu.org 2013-03-17 15:59:42 UTC ---
The patches of comment 2 and comment 3 regtest cleanly.


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

* [Bug fortran/56500] [OOP] "IMPLICIT CLASS(...)" wrongly rejected
  2013-03-01 18:07 [Bug fortran/56500] New: [OOP] "IMPLICIT CLASS(...)" wrongly rejected burnus at gcc dot gnu.org
                   ` (3 preceding siblings ...)
  2013-03-17 16:00 ` janus at gcc dot gnu.org
@ 2013-03-17 19:46 ` dominiq at lps dot ens.fr
  2013-03-17 21:02 ` janus at gcc dot gnu.org
                   ` (5 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: dominiq at lps dot ens.fr @ 2013-03-17 19:46 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #5 from Dominique d'Humieres <dominiq at lps dot ens.fr> 2013-03-17 19:46:16 UTC ---
> The patches of comment 2 and comment 3 regtest cleanly.

With the patches applied to a clean revision 196754 I have lot of errors in my
tests and at least one failure for the test suite:

[macbook] f90/bug% /opt/gcc/gcc4.9p-196754p1/bin/gfortran
/opt/gcc/work/gcc/testsuite/gfortran.dg/array_constructor_42.f90
/opt/gcc/work/gcc/testsuite/gfortran.dg/array_constructor_42.f90:13.21:

    intrinsic :: real
                     1
Error: Symbol 'real' at (1) has no IMPLICIT type
/opt/gcc/work/gcc/testsuite/gfortran.dg/array_constructor_42.f90:20.21:

    intrinsic :: real
                     1
Error: Symbol 'real' at (1) has no IMPLICIT type

The patch I have is

diff -up ../_clean/gcc/fortran/decl.c ../p_work/gcc/fortran/decl.c
--- ../_clean/gcc/fortran/decl.c    2013-02-02 11:15:07.000000000 +0100
+++ ../p_work/gcc/fortran/decl.c    2013-03-17 18:43:50.000000000 +0100
@@ -6293,6 +6293,13 @@ attr_decl1 (void)
     }
     }

+  if (sym->ts.type == BT_UNKNOWN
+      && gfc_set_default_type (sym, 1, NULL) == FAILURE)
+    {
+      m = MATCH_ERROR;
+      goto cleanup;
+    }
+
   /* Update symbol table.  DIMENSION attribute is set in
      gfc_set_array_spec().  For CLASS variables, this must be applied
      to the first component, or '_data' field.  */
diff -up ../_clean/gcc/fortran/resolve.c ../p_work/gcc/fortran/resolve.c
--- ../_clean/gcc/fortran/resolve.c    2013-03-10 14:25:57.000000000 +0100
+++ ../p_work/gcc/fortran/resolve.c    2013-03-17 18:43:50.000000000 +0100
@@ -318,7 +318,13 @@ resolve_formal_arglist (gfc_symbol *proc
     {
       if (sym->ts.type == BT_UNKNOWN && !proc->attr.intrinsic
           && (!sym->attr.function || sym->result == sym))
-        gfc_set_default_type (sym, 1, sym->ns);
+        {
+          gfc_set_default_type (sym, 1, sym->ns);
+          if (sym->ts.type == BT_CLASS
+          && gfc_build_class_symbol (&sym->ts, &sym->attr,
+                         &sym->as, false) == FAILURE)
+        continue;
+        }
     }

       as = sym->ts.type == BT_CLASS && sym->attr.class_ok

(the patch in comment #3 is rejected and I have applied it manually, may be I
made a mistake I cannot spot).


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

* [Bug fortran/56500] [OOP] "IMPLICIT CLASS(...)" wrongly rejected
  2013-03-01 18:07 [Bug fortran/56500] New: [OOP] "IMPLICIT CLASS(...)" wrongly rejected burnus at gcc dot gnu.org
                   ` (4 preceding siblings ...)
  2013-03-17 19:46 ` dominiq at lps dot ens.fr
@ 2013-03-17 21:02 ` janus at gcc dot gnu.org
  2013-03-17 21:30 ` dominiq at lps dot ens.fr
                   ` (4 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: janus at gcc dot gnu.org @ 2013-03-17 21:02 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #6 from janus at gcc dot gnu.org 2013-03-17 21:01:40 UTC ---
(In reply to comment #5)
> > The patches of comment 2 and comment 3 regtest cleanly.
> 
> With the patches applied to a clean revision 196754 I have lot of errors in my
> tests and at least one failure for the test suite:

Oops, you're right. *Lots* of failures. Seems I looked at the wrong logfile :(


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

* [Bug fortran/56500] [OOP] "IMPLICIT CLASS(...)" wrongly rejected
  2013-03-01 18:07 [Bug fortran/56500] New: [OOP] "IMPLICIT CLASS(...)" wrongly rejected burnus at gcc dot gnu.org
                   ` (5 preceding siblings ...)
  2013-03-17 21:02 ` janus at gcc dot gnu.org
@ 2013-03-17 21:30 ` dominiq at lps dot ens.fr
  2013-03-17 22:38 ` janus at gcc dot gnu.org
                   ` (3 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: dominiq at lps dot ens.fr @ 2013-03-17 21:30 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #7 from Dominique d'Humieres <dominiq at lps dot ens.fr> 2013-03-17 21:30:32 UTC ---
> Oops, you're right. *Lots* of failures. Seems I looked at the wrong logfile :(

AFAICT they come from the patch in comment #2 and are mostly (all?) of the kind
"... has no IMPLICIT type".


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

* [Bug fortran/56500] [OOP] "IMPLICIT CLASS(...)" wrongly rejected
  2013-03-01 18:07 [Bug fortran/56500] New: [OOP] "IMPLICIT CLASS(...)" wrongly rejected burnus at gcc dot gnu.org
                   ` (6 preceding siblings ...)
  2013-03-17 21:30 ` dominiq at lps dot ens.fr
@ 2013-03-17 22:38 ` janus at gcc dot gnu.org
  2013-03-18 12:17 ` dominiq at lps dot ens.fr
                   ` (2 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: janus at gcc dot gnu.org @ 2013-03-17 22:38 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #8 from janus at gcc dot gnu.org 2013-03-17 22:37:56 UTC ---
(In reply to comment #7)
> > Oops, you're right. *Lots* of failures. Seems I looked at the wrong logfile :(
> 
> AFAICT they come from the patch in comment #2 and are mostly (all?) of the kind
> "... has no IMPLICIT type".

Yes. I hope this variant should work better (regtesting now):


Index: gcc/fortran/decl.c
===================================================================
--- gcc/fortran/decl.c    (revision 196748)
+++ gcc/fortran/decl.c    (working copy)
@@ -6293,6 +6293,9 @@ attr_decl1 (void)
     }
     }

+  if (sym->ts.type == BT_UNKNOWN)
+      gfc_set_default_type (sym, 0, NULL);
+
   /* Update symbol table.  DIMENSION attribute is set in
      gfc_set_array_spec().  For CLASS variables, this must be applied
      to the first component, or '_data' field.  */


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

* [Bug fortran/56500] [OOP] "IMPLICIT CLASS(...)" wrongly rejected
  2013-03-01 18:07 [Bug fortran/56500] New: [OOP] "IMPLICIT CLASS(...)" wrongly rejected burnus at gcc dot gnu.org
                   ` (7 preceding siblings ...)
  2013-03-17 22:38 ` janus at gcc dot gnu.org
@ 2013-03-18 12:17 ` dominiq at lps dot ens.fr
  2013-03-18 12:57 ` janus at gcc dot gnu.org
  2013-04-01 15:34 ` janus at gcc dot gnu.org
  10 siblings, 0 replies; 12+ messages in thread
From: dominiq at lps dot ens.fr @ 2013-03-18 12:17 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #9 from Dominique d'Humieres <dominiq at lps dot ens.fr> 2013-03-18 12:16:59 UTC ---
> Yes. I hope this variant should work better (regtesting now):

It "works better", but still has regressions:

[macbook] f90/bug% gfc /opt/gcc/work/gcc/testsuite/gfortran.dg/proc_ptr_36.f90
/opt/gcc/work/gcc/testsuite/gfortran.dg/proc_ptr_36.f90:26.6:

pp => sub2
      1
Error: Interface mismatch in procedure pointer assignment at (1): 'sub2' is not
a function
/opt/gcc/work/gcc/testsuite/gfortran.dg/proc_ptr_36.f90:29.7:

call s(pp, .true.)
       1
Error: Interface mismatch in dummy procedure 'ss' at (1): 'pp' is not a
subroutine
/opt/gcc/work/gcc/testsuite/gfortran.dg/proc_ptr_36.f90:33.7:

call s(pp, .false.)
       1
Error: Interface mismatch in dummy procedure 'ss' at (1): 'pp' is not a
subroutine


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

* [Bug fortran/56500] [OOP] "IMPLICIT CLASS(...)" wrongly rejected
  2013-03-01 18:07 [Bug fortran/56500] New: [OOP] "IMPLICIT CLASS(...)" wrongly rejected burnus at gcc dot gnu.org
                   ` (8 preceding siblings ...)
  2013-03-18 12:17 ` dominiq at lps dot ens.fr
@ 2013-03-18 12:57 ` janus at gcc dot gnu.org
  2013-04-01 15:34 ` janus at gcc dot gnu.org
  10 siblings, 0 replies; 12+ messages in thread
From: janus at gcc dot gnu.org @ 2013-03-18 12:57 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #10 from janus at gcc dot gnu.org 2013-03-18 12:56:57 UTC ---
(In reply to comment #9)
> > Yes. I hope this variant should work better (regtesting now):
> 
> It "works better", but still has regressions:

Yes, I already noticed this. The following version should finally be
regression-free:


Index: gcc/fortran/decl.c
===================================================================
--- gcc/fortran/decl.c    (revision 196748)
+++ gcc/fortran/decl.c    (working copy)
@@ -6293,6 +6293,10 @@ attr_decl1 (void)
     }
     }

+  if (sym->ts.type == BT_UNKNOWN
+      && gfc_get_default_type (sym->name, NULL)->type == BT_CLASS)
+      gfc_set_default_type (sym, 0, NULL);
+
   /* Update symbol table.  DIMENSION attribute is set in
      gfc_set_array_spec().  For CLASS variables, this must be applied
      to the first component, or '_data' field.  */


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

* [Bug fortran/56500] [OOP] "IMPLICIT CLASS(...)" wrongly rejected
  2013-03-01 18:07 [Bug fortran/56500] New: [OOP] "IMPLICIT CLASS(...)" wrongly rejected burnus at gcc dot gnu.org
                   ` (9 preceding siblings ...)
  2013-03-18 12:57 ` janus at gcc dot gnu.org
@ 2013-04-01 15:34 ` janus at gcc dot gnu.org
  10 siblings, 0 replies; 12+ messages in thread
From: janus at gcc dot gnu.org @ 2013-04-01 15:34 UTC (permalink / raw)
  To: gcc-bugs


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

janus at gcc dot gnu.org changed:

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

--- Comment #11 from janus at gcc dot gnu.org 2013-04-01 15:34:40 UTC ---
Fixed with r197306:

http://gcc.gnu.org/viewcvs/gcc?view=revision&revision=197306

Closing.


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

end of thread, other threads:[~2013-04-01 15:34 UTC | newest]

Thread overview: 12+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2013-03-01 18:07 [Bug fortran/56500] New: [OOP] "IMPLICIT CLASS(...)" wrongly rejected burnus at gcc dot gnu.org
2013-03-02  0:07 ` [Bug fortran/56500] " burnus at gcc dot gnu.org
2013-03-17 12:55 ` janus at gcc dot gnu.org
2013-03-17 13:12 ` janus at gcc dot gnu.org
2013-03-17 16:00 ` janus at gcc dot gnu.org
2013-03-17 19:46 ` dominiq at lps dot ens.fr
2013-03-17 21:02 ` janus at gcc dot gnu.org
2013-03-17 21:30 ` dominiq at lps dot ens.fr
2013-03-17 22:38 ` janus at gcc dot gnu.org
2013-03-18 12:17 ` dominiq at lps dot ens.fr
2013-03-18 12:57 ` janus at gcc dot gnu.org
2013-04-01 15:34 ` janus 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).