public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/47805] New: [OOP] Overridding hidden (private) TPB is rejected
@ 2011-02-18 17:06 burnus at gcc dot gnu.org
  2011-02-18 17:07 ` [Bug fortran/47805] " burnus at gcc dot gnu.org
                   ` (4 more replies)
  0 siblings, 5 replies; 6+ messages in thread
From: burnus at gcc dot gnu.org @ 2011-02-18 17:06 UTC (permalink / raw)
  To: gcc-bugs

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

           Summary: [OOP] Overridding hidden (private) TPB is rejected
           Product: gcc
           Version: 4.6.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


See http://j3-fortran.org/doc/year/11/11-141.txt and watch out for updates
(11-141r1.txt etc.), approved by J3 meeting.

Overriding a TBP seems to OK, if the TBP is hidden through accessibility
(PRIVATE).

Note (cf. example 2 in the IR): Abstract DT with private deferred TBP cannot be
extended as one cannot implement the deferred TBP.


The first example given in the file is rejected with:

      PROCEDURE,NOPASS :: p => p2 ! (2).
               1
Error: 'p' at (1) must have the same number of formal arguments as the
overridden procedure


  MODULE example1_m1
    TYPE t1
    CONTAINS
      PROCEDURE,PRIVATE,NOPASS :: p ! (1).
    END TYPE
  CONTAINS
    SUBROUTINE p
      PRINT *,'p'
    END SUBROUTINE
    SUBROUTINE do_p(x)
      CLASS(t1) x
      CALL x%p
    END SUBROUTINE
  END MODULE
  MODULE example1_m2
    USE example1_m1
    TYPE,EXTENDS(t1) :: t2
    CONTAINS
      PROCEDURE,NOPASS :: p => p2 ! (2).
    END TYPE
  CONTAINS
    SUBROUTINE p2(n)
      PRINT *,'p2',n
    END SUBROUTINE
  END MODULE
  PROGRAM example1
    USE example1_m2
    TYPE(t2),TARGET :: x
    CLASS(t1),POINTER :: y
    y => x
    CALL do_p(x) ! (3): I expect this to print 'p'.
    CALL do_p(y) ! (4): I expect this to print 'p'.
    CALL x%p(13) ! (5): I expect this to print 'p2 13'.
  END PROGRAM


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

* [Bug fortran/47805] [OOP] Overridding hidden (private) TPB is rejected
  2011-02-18 17:06 [Bug fortran/47805] New: [OOP] Overridding hidden (private) TPB is rejected burnus at gcc dot gnu.org
@ 2011-02-18 17:07 ` burnus at gcc dot gnu.org
  2011-02-19 11:26 ` janus at gcc dot gnu.org
                   ` (3 subsequent siblings)
  4 siblings, 0 replies; 6+ messages in thread
From: burnus at gcc dot gnu.org @ 2011-02-18 17:07 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #1 from Tobias Burnus <burnus at gcc dot gnu.org> 2011-02-18 17:05:35 UTC ---
Forgot to link to http://j3-fortran.org/pipermail/j3/2011-February/004197.html
which is about the J3 ballot of those items; it also contains an updated
version of the paper.

The IR has been approved by the J3 meeting and currently a J3 ballot is running
(cf. link); if accepted, it moves on to June's WG5 meeting in Garching.


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

* [Bug fortran/47805] [OOP] Overridding hidden (private) TPB is rejected
  2011-02-18 17:06 [Bug fortran/47805] New: [OOP] Overridding hidden (private) TPB is rejected burnus at gcc dot gnu.org
  2011-02-18 17:07 ` [Bug fortran/47805] " burnus at gcc dot gnu.org
@ 2011-02-19 11:26 ` janus at gcc dot gnu.org
  2011-02-19 14:23 ` janus at gcc dot gnu.org
                   ` (2 subsequent siblings)
  4 siblings, 0 replies; 6+ messages in thread
From: janus at gcc dot gnu.org @ 2011-02-19 11:26 UTC (permalink / raw)
  To: gcc-bugs

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

janus at gcc dot gnu.org changed:

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

--- Comment #2 from janus at gcc dot gnu.org 2011-02-19 10:41:13 UTC ---
(In reply to comment #0)
> Overriding a TBP seems to OK, if the TBP is hidden through accessibility
> (PRIVATE).

Huh, tricky thing.



> The first example given in the file is rejected with:
> 
>       PROCEDURE,NOPASS :: p => p2 ! (2).
>                1
> Error: 'p' at (1) must have the same number of formal arguments as the
> overridden procedure


One can get rid of this error message e.g. by ... (warning: not regtested)


Index: class.c
===================================================================
--- class.c     (revision 170290)
+++ class.c     (working copy)
@@ -639,21 +639,24 @@
   res = gfc_find_symtree (root, name);
   if (res && res->n.tb && !res->n.tb->error)
     {
-      /* We found one.  */
-      if (t)
-       *t = SUCCESS;
-
       if (!noaccess && derived->attr.use_assoc
          && res->n.tb->access == ACCESS_PRIVATE)
        {
          if (where)
-           gfc_error ("'%s' of '%s' is PRIVATE at %L",
-                      name, derived->name, where);
+           {
+             gfc_error ("'%s' of '%s' is PRIVATE at %L",
+                        name, derived->name, where);
+             return res;
+           }
+       }
+      else
+       {
+         /* We found one.  */
          if (t)
-           *t = FAILURE;
+           *t = SUCCESS;
+
+         return res;
        }
-
-      return res;
     }

   /* Otherwise, recurse on parent type if derived is an extension.  */
Index: resolve.c
===================================================================
--- resolve.c   (revision 170290)
+++ resolve.c   (working copy)
@@ -11194,8 +11194,8 @@
   if (super_type)
     {
       gfc_symtree* overridden;
-      overridden = gfc_find_typebound_proc (super_type, NULL,
-                                           stree->name, true, NULL);
+      overridden = gfc_find_typebound_proc (super_type, NULL, stree->name,
+                                           false, NULL);

       if (overridden && overridden->n.tb)
        stree->n.tb->overridden = overridden->n.tb;



However, one then gets different results than indicated in (3)-(5), i.e.
gfortran always calls 'p2'. It seems our current run-time mechanisms are not
able to cope with this case.

The only way I can see out of this is to resolve the call in 'do_p' not to the
polymorphic version 'x->_vptr->p', but to a static call to the subroutine 'p'
(since 'p' is effectively not overridable, at least not outside the module).

But then it gets really tricky if we put 't2' in the same module. Then 'p'
*will* be overridden, and we have to get back to the dynamic vtable call again
to get it right.

Then be so nasty to add another type 't3' in a different module, which defines
a new TBP 'p' which does *not* override t1%p. And, bang!, we're in trouble
again.

So, I'm clueless. Does it help to put the type-name into the binding name? Say,
have the call in 'do_p' resolve to 'x->_vptr->t1_p' (to honor the fact that the
base type for the call is t1).


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

* [Bug fortran/47805] [OOP] Overridding hidden (private) TPB is rejected
  2011-02-18 17:06 [Bug fortran/47805] New: [OOP] Overridding hidden (private) TPB is rejected burnus at gcc dot gnu.org
  2011-02-18 17:07 ` [Bug fortran/47805] " burnus at gcc dot gnu.org
  2011-02-19 11:26 ` janus at gcc dot gnu.org
@ 2011-02-19 14:23 ` janus at gcc dot gnu.org
  2012-10-01 13:49 ` burnus at gcc dot gnu.org
  2015-10-13 16:55 ` dominiq at lps dot ens.fr
  4 siblings, 0 replies; 6+ messages in thread
From: janus at gcc dot gnu.org @ 2011-02-19 14:23 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #3 from janus at gcc dot gnu.org 2011-02-19 13:57:09 UTC ---
(In reply to comment #2)
> One can get rid of this error message e.g. by ... (warning: not regtested)

Side note: This patch does not cause any regressions in the test suite.
However, it makes no sense to apply it without any run-time support for this
feature (which will be less trivial to implement). Also one should probably
wait for the final result of the interpretation request, which means this will
probably not make it into 4.6.


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

* [Bug fortran/47805] [OOP] Overridding hidden (private) TPB is rejected
  2011-02-18 17:06 [Bug fortran/47805] New: [OOP] Overridding hidden (private) TPB is rejected burnus at gcc dot gnu.org
                   ` (2 preceding siblings ...)
  2011-02-19 14:23 ` janus at gcc dot gnu.org
@ 2012-10-01 13:49 ` burnus at gcc dot gnu.org
  2015-10-13 16:55 ` dominiq at lps dot ens.fr
  4 siblings, 0 replies; 6+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-10-01 13:49 UTC (permalink / raw)
  To: gcc-bugs


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

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

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

--- Comment #4 from Tobias Burnus <burnus at gcc dot gnu.org> 2012-10-01 13:48:48 UTC ---
Updated version: F08/0052 at ftp://ftp.nag.co.uk/sc22wg5/N1901-N1950/N1907.txt
(incorporated in Corrigendum 1 to F2008).


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

* [Bug fortran/47805] [OOP] Overridding hidden (private) TPB is rejected
  2011-02-18 17:06 [Bug fortran/47805] New: [OOP] Overridding hidden (private) TPB is rejected burnus at gcc dot gnu.org
                   ` (3 preceding siblings ...)
  2012-10-01 13:49 ` burnus at gcc dot gnu.org
@ 2015-10-13 16:55 ` dominiq at lps dot ens.fr
  4 siblings, 0 replies; 6+ messages in thread
From: dominiq at lps dot ens.fr @ 2015-10-13 16:55 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=47805

Dominique d'Humieres <dominiq at lps dot ens.fr> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
   Last reconfirmed|                            |2015-10-13
     Ever confirmed|0                           |1

--- Comment #5 from Dominique d'Humieres <dominiq at lps dot ens.fr> ---
For what it worth, updated link in comment 1:

http://mailman.j3-fortran.org/pipermail/j3/2011-February/004197.html

The problems are still there at r228753.


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

end of thread, other threads:[~2015-10-13 16:55 UTC | newest]

Thread overview: 6+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2011-02-18 17:06 [Bug fortran/47805] New: [OOP] Overridding hidden (private) TPB is rejected burnus at gcc dot gnu.org
2011-02-18 17:07 ` [Bug fortran/47805] " burnus at gcc dot gnu.org
2011-02-19 11:26 ` janus at gcc dot gnu.org
2011-02-19 14:23 ` janus at gcc dot gnu.org
2012-10-01 13:49 ` burnus at gcc dot gnu.org
2015-10-13 16:55 ` dominiq at lps dot ens.fr

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).