public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/46313] New: [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue
@ 2010-11-05 14:44 burnus at gcc dot gnu.org
  2010-11-05 15:47 ` [Bug fortran/46313] " kargl at gcc dot gnu.org
                   ` (25 more replies)
  0 siblings, 26 replies; 27+ messages in thread
From: burnus at gcc dot gnu.org @ 2010-11-05 14:44 UTC (permalink / raw)
  To: gcc-bugs

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

           Summary: [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming
                    issue
           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


There are a couple of issues which prevent the following program from working.

(a) and (b) are compile time issues and (c) is a link-time issue (OOP ABI)


a) It fails to compile with: 

allocate ( t1 :: a1)
          1
Error: Error in type-spec at (1)


b) Working around this issue, as in

allocate (a1, source=t1())
allocate (b1, source=t2())

yields the error 

print *, b2%b
             1
Error: 'b' at (1) is not a member of the 'mytype' structure


Using Cray ftn, the result is:
 10*2.
 10*8.

!----------------------------------------

module m1
  type mytype
    real :: a(10) = 2
  end type mytype
end module m1

module m2
  type mytype
    real :: b(10) = 8
  end type mytype
end module m2

use m1, t1 => mytype
use m2, t2 => mytype
implicit none
class(t1), allocatable :: a1, a2
class(t2), allocatable :: b1, b2

allocate ( t1 :: a1)
allocate ( t2 :: b1)

allocate ( a2, source=a1)
allocate ( b2, source=b1)
!allocate ( a2, mold=a1)
!allocate ( b2, mold=b1)
print *, a2%a
print *, b2%b
end
!----------------------------------------



(c) The following fails to link as the VTABLE only encodes the type name and
not the module name:

/tmp/ccBQh5fR.s: Assembler messages:
/tmp/ccBQh5fR.s:401: Error: symbol `copy$mytype2_' is already defined
/tmp/ccBQh5fR.s:431: Error: symbol `copy$mytype_' is already defined


!----------------------------------------
module m1
  implicit none
  type mytype
  end type mytype
  type,extends(mytype) :: mytype2
    integer :: a(10) = 2
  end type mytype2
contains
  subroutine test1()
    class(mytype), allocatable :: a1, a2
    allocate (a1, source=mytype2())
    allocate ( a2, source=a1)
    select type (a2)
      type is (mytype2)
        print *, a2%a
    end select
    deallocate  (a2)
    allocate ( a2, mold=a1)
    select type (a2)
      type is (mytype2)
        print *, a2%a
    end select
  end subroutine test1
end module m1

module m2
  implicit none
  type mytype
  end type mytype
  type,extends(mytype) :: mytype2
    integer :: b(10) = 8
  end type mytype2
contains
  subroutine test2()
    class(mytype), allocatable :: b1, b2
    allocate (b1, source=mytype2())
    allocate ( b2, source=b1)
    select type (b2)
      type is (mytype2)
        print *, b2%b
    end select
    deallocate  (b2)
    allocate ( b2, mold=b1)
    select type (b2)
      type is (mytype2)
        print *, b2%b
    end select
  end subroutine test2
end module m2

use m1, only: test1
use m2, only: test2
implicit none
call test1()
call test2()
end
!----------------------------------------


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

* [Bug fortran/46313] [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue
  2010-11-05 14:44 [Bug fortran/46313] New: [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue burnus at gcc dot gnu.org
@ 2010-11-05 15:47 ` kargl at gcc dot gnu.org
  2010-11-05 16:04 ` sgk at troutmask dot apl.washington.edu
                   ` (24 subsequent siblings)
  25 siblings, 0 replies; 27+ messages in thread
From: kargl at gcc dot gnu.org @ 2010-11-05 15:47 UTC (permalink / raw)
  To: gcc-bugs

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

kargl at gcc dot gnu.org changed:

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

--- Comment #1 from kargl at gcc dot gnu.org 2010-11-05 15:46:10 UTC ---
With r166360, I do not see the (a) problem.  Are you using a
clean source tree or do you have local changes?  For the
first code, I see

troutmask:sgk[209] gfc4x -o z tr.f90
tr.f90:20.17:

allocate ( t2 :: b1)
                 1
Error: Type of entity at (1) is type incompatible with typespec
tr.f90:27.13:

print *, b2%b
             1
Error: 'b' at (1) is not a member of the 'mytype' structure


I'll also note that your (b) workaround fails with

troutmask:sgk[240] gfc4x -o z tr.f90
tr.f90:27.13:

print *, b2%b
             1
Error: 'b' at (1) is not a member of the 'mytype' structure
tr.f90:20.10-21:

allocate (b1, source=t2())
          1          2
Error: Type of entity at (1) is type incompatible with source-expr at (2)

-fdump-parse-tree suggests that the parsing of class(t2) :: b1, b2
is not picking up the renamed type.

Namespace: A-Z: (UNKNOWN 0)
procedure name = MAIN__
  symtree: 'MAIN__'      || symbol: 'MAIN__'       
    type spec : (UNKNOWN 0)
    attributes: (PROGRAM PUBLIC  SUBROUTINE)
  symtree: 'a1'          || symbol: 'a1'           
    type spec : (CLASS class$mytype_a)
    attributes: (VARIABLE )
    value: class$mytype_a(NULL() , ())
  symtree: 'a2'          || symbol: 'a2'           
    type spec : (CLASS class$mytype_a)
    attributes: (VARIABLE )
    value: class$mytype_a(NULL() , ())
  symtree: 'b1'          || symbol: 'b1'           
    type spec : (CLASS class$mytype_a)
    attributes: (VARIABLE )
    value: class$mytype_a(NULL() , ())
  symtree: 'b2'          || symbol: 'b2'           
    type spec : (CLASS class$mytype_a)
    attributes: (VARIABLE )
    value: class$mytype_a(NULL() , ())
  symtree: 'class$mytype_a'|| symbol: 'class$mytype_a' 
    type spec : (UNKNOWN 0)
    attributes: (DERIVED )
    components: ($data (DERIVED mytype) () PRIVATE)
                ($vptr (DERIVED vtype$mytype) POINTER () PRIVATE)

    Procedure bindings:
    Operator bindings:
  symtree: 'def_init$mytype'|| symbol: 'def_init$mytype' 
    type spec : (DERIVED mytype)
    attributes: (VARIABLE PUBLIC EXPLICIT-SAVE TARGET)
    value: mytype(2.00000000)
  symtree: 'm1'          || symbol: 'm1'           
    type spec : (UNKNOWN 0)
    attributes: (MODULE  USE-ASSOC(m1))
  symtree: 'm2'          || symbol: 'm2'           
    type spec : (UNKNOWN 0)
    attributes: (MODULE  USE-ASSOC(m2))
  symtree: 't1'          || symbol: 'mytype'       
    type spec : (UNKNOWN 0)
    attributes: (DERIVED  USE-ASSOC(m1))
    components: (a (REAL 4) DIMENSION (1 [0] AS_EXPLICIT 1 10 ))
    hash: 22483813
    Procedure bindings:
    Operator bindings:
  symtree: 't2'          || symbol: 'mytype'       
    type spec : (UNKNOWN 0)
    attributes: (DERIVED  USE-ASSOC(m2))
    components: (b (REAL 4) DIMENSION (1 [0] AS_EXPLICIT 1 10 ))
    hash: 58329636
    Procedure bindings:
    Operator bindings:
  symtree: 'vtab$mytype' || symbol: 'vtab$mytype'  
    type spec : (DERIVED vtype$mytype)
    attributes: (VARIABLE PUBLIC EXPLICIT-SAVE TARGET)
    value: vtype$mytype(22483813 , 0 , NULL() , MAIN__:def_init$mytype)
  symtree: 'vtype$mytype'|| symbol: 'vtype$mytype' 
    type spec : (UNKNOWN 0)
    attributes: (DERIVED PUBLIC )
    components: ($hash (INTEGER 4) () PRIVATE)
                ($size (INTEGER 4) () PRIVATE)
                ($extends (DERIVED vtype$mytype) POINTER () PRIVATE)
                ($def_init (DERIVED mytype) POINTER () PRIVATE)

  code:
  ALLOCATE  MAIN__:a1
  ALLOCATE  MAIN__:b1
  ALLOCATE  MAIN__:a2
  ALLOCATE  MAIN__:b2
  WRITE UNIT=6 FMT=-1
  TRANSFER MAIN__:a2 % a(FULL)
  DT_END

Finally, note that if you rename mytype in either module to
something unique, then the code compiles.


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

* [Bug fortran/46313] [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue
  2010-11-05 14:44 [Bug fortran/46313] New: [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue burnus at gcc dot gnu.org
  2010-11-05 15:47 ` [Bug fortran/46313] " kargl at gcc dot gnu.org
@ 2010-11-05 16:04 ` sgk at troutmask dot apl.washington.edu
  2010-11-06  0:38 ` kargl at gcc dot gnu.org
                   ` (23 subsequent siblings)
  25 siblings, 0 replies; 27+ messages in thread
From: sgk at troutmask dot apl.washington.edu @ 2010-11-05 16:04 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #2 from Steve Kargl <sgk at troutmask dot apl.washington.edu> 2010-11-05 16:04:31 UTC ---
On Fri, Nov 05, 2010 at 03:46:14PM +0000, kargl at gcc dot gnu.org wrote:
> 
> -fdump-parse-tree suggests that the parsing of class(t2) :: b1, b2
> is not picking up the renamed type.
> 

I think allocate() is doing its job.  This looks like class()
is getting confused by the rename.

module m1
  type mytype
    integer :: a(10) = 2
    integer :: b(10) = 3
  end type mytype
end module m1

module m2
  type mytype
    real :: a(10) = 8
    real :: b(10) = 9
  end type mytype
end module m2

program testing
  use m1, t1 => mytype
  use m2, t2 => mytype

  implicit none

  class(t1), allocatable :: a1
  class(t2), allocatable :: b1
  allocate(a1, b1)
  print '(10(I0,1X))', a1%a
  print '(10(I0,1X))', b1%b
end program testing

troutmask:sgk[203] gfc4x -o z tr.f90 && ./z
2 2 2 2 2 2 2 2 2 2
3 3 3 3 3 3 3 3 3 3


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

* [Bug fortran/46313] [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue
  2010-11-05 14:44 [Bug fortran/46313] New: [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue burnus at gcc dot gnu.org
  2010-11-05 15:47 ` [Bug fortran/46313] " kargl at gcc dot gnu.org
  2010-11-05 16:04 ` sgk at troutmask dot apl.washington.edu
@ 2010-11-06  0:38 ` kargl at gcc dot gnu.org
  2010-11-06 15:26 ` janus at gcc dot gnu.org
                   ` (22 subsequent siblings)
  25 siblings, 0 replies; 27+ messages in thread
From: kargl at gcc dot gnu.org @ 2010-11-06  0:38 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #3 from kargl at gcc dot gnu.org 2010-11-06 00:37:47 UTC ---
(In reply to comment #1)
>
> Namespace: A-Z: (UNKNOWN 0)
> procedure name = MAIN__
>   symtree: 'MAIN__'      || symbol: 'MAIN__'       
>     type spec : (UNKNOWN 0)
>     attributes: (PROGRAM PUBLIC  SUBROUTINE)
>   symtree: 'a1'          || symbol: 'a1'           
>     type spec : (CLASS class$mytype_a)
>     attributes: (VARIABLE )
>     value: class$mytype_a(NULL() , ())
>   symtree: 'a2'          || symbol: 'a2'           
>     type spec : (CLASS class$mytype_a)
>     attributes: (VARIABLE )
>     value: class$mytype_a(NULL() , ())
>   symtree: 'b1'          || symbol: 'b1'           
>     type spec : (CLASS class$mytype_a)
>     attributes: (VARIABLE )
>     value: class$mytype_a(NULL() , ())
>   symtree: 'b2'          || symbol: 'b2'           
>     type spec : (CLASS class$mytype_a)
>     attributes: (VARIABLE )
>     value: class$mytype_a(NULL() , ())

After staring at the -fdump-parse-tree, I realized that
everything is referencing mytype.  Shouldn't the 
symtrees for a1 and a2 reference t1 and the symtrees
for b1 and b2 reference t2?  That is,

   symtree: 'a1'          || symbol: 'a1'           
     type spec : (CLASS class$t1_a)
     attributes: (VARIABLE )
     value: class$mytype_a(NULL() , ())

-- 
steve


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

* [Bug fortran/46313] [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue
  2010-11-05 14:44 [Bug fortran/46313] New: [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue burnus at gcc dot gnu.org
                   ` (2 preceding siblings ...)
  2010-11-06  0:38 ` kargl at gcc dot gnu.org
@ 2010-11-06 15:26 ` janus at gcc dot gnu.org
  2010-11-09 10:40 ` janus at gcc dot gnu.org
                   ` (21 subsequent siblings)
  25 siblings, 0 replies; 27+ messages in thread
From: janus at gcc dot gnu.org @ 2010-11-06 15:26 UTC (permalink / raw)
  To: gcc-bugs

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

janus at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |ASSIGNED
   Last reconfirmed|                            |2010.11.06 15:26:39
         AssignedTo|unassigned at gcc dot       |janus at gcc dot gnu.org
                   |gnu.org                     |
     Ever Confirmed|0                           |1

--- Comment #4 from janus at gcc dot gnu.org 2010-11-06 15:26:39 UTC ---
(In reply to comment #0)
> (c) The following fails to link as the VTABLE only encodes the type name and
> not the module name:

Yes, the basic problem here is our naming scheme for class containers, vtabs,
etc. It currently only contains the type name. When also including the module
name, both test cases work.

I'll post a patch soon.


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

* [Bug fortran/46313] [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue
  2010-11-05 14:44 [Bug fortran/46313] New: [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue burnus at gcc dot gnu.org
                   ` (3 preceding siblings ...)
  2010-11-06 15:26 ` janus at gcc dot gnu.org
@ 2010-11-09 10:40 ` janus at gcc dot gnu.org
  2010-11-09 11:54 ` janus at gcc dot gnu.org
                   ` (20 subsequent siblings)
  25 siblings, 0 replies; 27+ messages in thread
From: janus at gcc dot gnu.org @ 2010-11-09 10:40 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #5 from janus at gcc dot gnu.org 2010-11-09 10:39:52 UTC ---
Author: janus
Date: Tue Nov  9 10:39:46 2010
New Revision: 166480

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=166480
Log:
2010-11-09  Janus Weil  <janus@gcc.gnu.org>

    PR fortran/46313
    * gfortran.h (gfc_add_data_component,gfc_add_vptr_component,
    gfc_add_hash_component,gfc_add_size_component,
    gfc_add_def_init_component): New macros.
    * class.c (gfc_add_component_ref): Renamed data component.
    (get_unique_type_string): New function.
    (gfc_build_class_symbol): Use 'get_unique_type_string' to construct
    uniques names for the class containers. Rename components.
    (gfc_find_derived_vtab): Use 'get_unique_type_string' to construct
    uniques names for the vtab symbols. Rename components.
    * decl.c (attr_decl1): Renamed class container components.
    * iresolve.c (gfc_resolve_extends_type_of): Ditto.
    * match.c (select_type_set_tmp): Renamed temporaries.
    * module.c (read_module): Renamed vtab and vtype symbols.
    * resolve.c (resolve_structure_cons,resolve_typebound_function,
    resolve_typebound_subroutine,resolve_deallocate_expr,
    resolve_select_type,resolve_fl_derived): Renamed class container and
    vtab components.
    * trans-array.c (structure_alloc_comps): Ditto.
    * trans-decl.c (gfc_trans_deferred_vars): Ditto.
    * trans-expr.c (gfc_conv_derived_to_class,gfc_conv_structure,
    gfc_trans_class_init_assign,gfc_trans_class_assign): Ditto.
    * trans-intrinsic.c (gfc_conv_intrinsic_sizeof,
    gfc_conv_intrinsic_storage_size,gfc_conv_allocated,gfc_conv_associated,
    gfc_conv_same_type_as): Ditto.
    * trans-stmt.c (gfc_trans_allocate): Ditto.

2010-11-09  Janus Weil  <janus@gcc.gnu.org>

    PR fortran/46313
    * gfortran.dg/class_29.f03: New.

Added:
    trunk/gcc/testsuite/gfortran.dg/class_29.f03
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/class.c
    trunk/gcc/fortran/decl.c
    trunk/gcc/fortran/gfortran.h
    trunk/gcc/fortran/iresolve.c
    trunk/gcc/fortran/match.c
    trunk/gcc/fortran/module.c
    trunk/gcc/fortran/resolve.c
    trunk/gcc/fortran/trans-array.c
    trunk/gcc/fortran/trans-decl.c
    trunk/gcc/fortran/trans-expr.c
    trunk/gcc/fortran/trans-intrinsic.c
    trunk/gcc/fortran/trans-stmt.c
    trunk/gcc/testsuite/ChangeLog


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

* [Bug fortran/46313] [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue
  2010-11-05 14:44 [Bug fortran/46313] New: [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue burnus at gcc dot gnu.org
                   ` (4 preceding siblings ...)
  2010-11-09 10:40 ` janus at gcc dot gnu.org
@ 2010-11-09 11:54 ` janus at gcc dot gnu.org
  2010-11-09 12:52 ` [Bug fortran/46313] [OOP] class container naming collisions janus at gcc dot gnu.org
                   ` (19 subsequent siblings)
  25 siblings, 0 replies; 27+ messages in thread
From: janus at gcc dot gnu.org @ 2010-11-09 11:54 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #6 from janus at gcc dot gnu.org 2010-11-09 11:54:18 UTC ---
r166480 fixes the original test case.

As Tobias pointed out at

http://gcc.gnu.org/ml/fortran/2010-11/msg00120.html

there may be additional problems when defining derived types in
procedures/submodules.


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

* [Bug fortran/46313] [OOP] class container naming collisions
  2010-11-05 14:44 [Bug fortran/46313] New: [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue burnus at gcc dot gnu.org
                   ` (5 preceding siblings ...)
  2010-11-09 11:54 ` janus at gcc dot gnu.org
@ 2010-11-09 12:52 ` janus at gcc dot gnu.org
  2010-11-09 13:52 ` burnus at gcc dot gnu.org
                   ` (18 subsequent siblings)
  25 siblings, 0 replies; 27+ messages in thread
From: janus at gcc dot gnu.org @ 2010-11-09 12:52 UTC (permalink / raw)
  To: gcc-bugs

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

janus at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
            Summary|[OOP] OOP-ABI issue,        |[OOP] class container
                   |ALLOCATE issue, CLASS       |naming collisions
                   |renaming issue              |

--- Comment #7 from janus at gcc dot gnu.org 2010-11-09 12:52:12 UTC ---
(In reply to comment #6)
> As Tobias pointed out at
> 
> http://gcc.gnu.org/ml/fortran/2010-11/msg00120.html
> 
> there may be additional problems when defining derived types in
> procedures/submodules.


Here is an example code which still fails (analogous to comment #0):


module m
  type t
    real :: a(10) = 2
  end type
end module


program p

  implicit none

  call m

contains

  subroutine m
    use m, t1 => t

    type t
      real :: b(10) = 8
    end type

    class(t1), allocatable :: x
    class(t), allocatable :: y

    allocate (t1 :: x)
    allocate (t :: y)

    print *, x%a
    print *, y%b
  end subroutine

end


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

* [Bug fortran/46313] [OOP] class container naming collisions
  2010-11-05 14:44 [Bug fortran/46313] New: [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue burnus at gcc dot gnu.org
                   ` (6 preceding siblings ...)
  2010-11-09 12:52 ` [Bug fortran/46313] [OOP] class container naming collisions janus at gcc dot gnu.org
@ 2010-11-09 13:52 ` burnus at gcc dot gnu.org
  2010-11-09 16:32 ` janus at gcc dot gnu.org
                   ` (17 subsequent siblings)
  25 siblings, 0 replies; 27+ messages in thread
From: burnus at gcc dot gnu.org @ 2010-11-09 13:52 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #8 from Tobias Burnus <burnus at gcc dot gnu.org> 2010-11-09 13:51:39 UTC ---
For completeness: The issues reported in comment 0 were all [(a), (b), and (c)]
due to same problem: The internal class symbols only encoded the derived-type
name.

This has been fixed by the commit in comment 5 by including the module name or
the procedure name in the vtable. As comment 6 and 7 show, one can carefully
craft a test case which will break.

To fix: modify get_unique_type_string for those cases - possibly without
breaking the ABI for derived-types declared in the declaration part of a module
(= common case).


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

* [Bug fortran/46313] [OOP] class container naming collisions
  2010-11-05 14:44 [Bug fortran/46313] New: [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue burnus at gcc dot gnu.org
                   ` (7 preceding siblings ...)
  2010-11-09 13:52 ` burnus at gcc dot gnu.org
@ 2010-11-09 16:32 ` janus at gcc dot gnu.org
  2010-11-09 17:07 ` janus at gcc dot gnu.org
                   ` (16 subsequent siblings)
  25 siblings, 0 replies; 27+ messages in thread
From: janus at gcc dot gnu.org @ 2010-11-09 16:32 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #9 from janus at gcc dot gnu.org 2010-11-09 16:32:16 UTC ---
(In reply to comment #7)
> Here is an example code which still fails (analogous to comment #0):

One way to fix this is to use the top-level namespace (i.e. program or module)
for the naming of the internal symbols, instead of the direct parent namespace
of the derived type (patch below).



Index: gcc/fortran/class.c
===================================================================
--- gcc/fortran/class.c (revision 166480)
+++ gcc/fortran/class.c (working copy)
@@ -117,7 +117,14 @@ get_unique_type_string (char *string, gfc_symbol *
   if (derived->module)
     sprintf (string, "%s_%s", derived->module, derived->name);
   else
-    sprintf (string, "%s_%s", derived->ns->proc_name->name, derived->name);
+    {
+      gfc_namespace *ns;
+      /* Find the top-level namespace (MODULE or PROGRAM).  */
+      for (ns = derived->ns; ns; ns = ns->parent)
+       if (!ns->parent)
+         break;
+      sprintf (string, "%s_%s", ns->proc_name->name, derived->name);
+    }
 }


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

* [Bug fortran/46313] [OOP] class container naming collisions
  2010-11-05 14:44 [Bug fortran/46313] New: [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue burnus at gcc dot gnu.org
                   ` (8 preceding siblings ...)
  2010-11-09 16:32 ` janus at gcc dot gnu.org
@ 2010-11-09 17:07 ` janus at gcc dot gnu.org
  2010-11-09 17:59 ` janus at gcc dot gnu.org
                   ` (15 subsequent siblings)
  25 siblings, 0 replies; 27+ messages in thread
From: janus at gcc dot gnu.org @ 2010-11-09 17:07 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #10 from janus at gcc dot gnu.org 2010-11-09 17:07:24 UTC ---
(In reply to comment #9)
> One way to fix this is to use the top-level namespace (i.e. program or module)
> for the naming of the internal symbols, instead of the direct parent namespace
> of the derived type (patch below).

Problem: This scheme produces wrong results for the following test case (which
is similar to comment #0, case c), since the vtabs for both types coincide:


implicit none

call test1()
call test2()

contains

  subroutine test1()
    type :: mytype
      integer :: a = 2
    end type mytype
    class(mytype), allocatable :: a1, a2
    print *,"test1"
    allocate (a1, source=mytype())
    allocate ( a2, source=a1)
    print *, a2%a
    deallocate  (a2)
    allocate ( a2, mold=a1)
    print *, a2%a
  end subroutine test1

  subroutine test2()
    type :: mytype
      integer :: b = 8
    end type mytype
    class(mytype), allocatable :: b1, b2
    print *,"test2"
    allocate (b1, source=mytype())
    allocate ( b2, source=b1)
    print *, b2%b
    deallocate  (b2)
    allocate ( b2, mold=b1)
    print *, b2%b
  end subroutine test2

end


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

* [Bug fortran/46313] [OOP] class container naming collisions
  2010-11-05 14:44 [Bug fortran/46313] New: [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue burnus at gcc dot gnu.org
                   ` (9 preceding siblings ...)
  2010-11-09 17:07 ` janus at gcc dot gnu.org
@ 2010-11-09 17:59 ` janus at gcc dot gnu.org
  2010-11-09 18:16 ` burnus at gcc dot gnu.org
                   ` (14 subsequent siblings)
  25 siblings, 0 replies; 27+ messages in thread
From: janus at gcc dot gnu.org @ 2010-11-09 17:59 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #11 from janus at gcc dot gnu.org 2010-11-09 17:59:04 UTC ---
(In reply to comment #10)
> > One way to fix this is to use the top-level namespace (i.e. program or module)
> > for the naming of the internal symbols, instead of the direct parent namespace
> > of the derived type (patch below).
> 
> Problem: This scheme produces wrong results for the following test case (which
> is similar to comment #0, case c), since the vtabs for both types coincide#:


... which can be fixed by including in the naming scheme the complete namespace
hierarchy (new patch below). This will definitely be unique. Downside: Can
result in long names (although I think it's most common to define derived types
globally in a module or program). Note: Also the hash value must be computed
from this full unique name, not just from the type name.


Index: gcc/fortran/class.c
===================================================================
--- gcc/fortran/class.c (revision 166480)
+++ gcc/fortran/class.c (working copy)
@@ -117,7 +118,19 @@ get_unique_type_string (char *string, gfc_symbol *
   if (derived->module)
     sprintf (string, "%s_%s", derived->module, derived->name);
   else
-    sprintf (string, "%s_%s", derived->ns->proc_name->name, derived->name);
+    {
+      gfc_namespace *ns;
+      char tmp[GFC_MAX_SYMBOL_LEN];
+      strcpy (&tmp[0], derived->name);
+      /* Walk namespace hierarchy.  */
+      for (ns = derived->ns; ns; ns = ns->parent)
+       {
+         sprintf (string, "%s_%s", ns->proc_name->name, tmp);
+         strcpy (&tmp[0], string);
+         if (!ns->parent)
+           break;
+       }
+    }
 }


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

* [Bug fortran/46313] [OOP] class container naming collisions
  2010-11-05 14:44 [Bug fortran/46313] New: [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue burnus at gcc dot gnu.org
                   ` (10 preceding siblings ...)
  2010-11-09 17:59 ` janus at gcc dot gnu.org
@ 2010-11-09 18:16 ` burnus at gcc dot gnu.org
  2010-11-09 18:24 ` burnus at gcc dot gnu.org
                   ` (13 subsequent siblings)
  25 siblings, 0 replies; 27+ messages in thread
From: burnus at gcc dot gnu.org @ 2010-11-09 18:16 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #12 from Tobias Burnus <burnus at gcc dot gnu.org> 2010-11-09 18:16:06 UTC ---
I think one needs to add all names to the namespace:

   <module>_<subroutine>_<internal-sub>_<type>
   <module>_<submodule-1>_<submodule-2>_<type>
etc. (Note: This can give extremely long variable names; I am not sure how
assemblers handle those.)

Note: I see an additional issue with the current scheme.

module one
  type two_three
  end type two_three
end module one

module one_two
  type three
  end type three
end module one_two

use one_two
class(two_three), allocatable :: a1
class(three), allocatable :: a2
end

produce the same __vtable entry. Names not possible in Fortran are "."
(period), capital letters (A-Z) and $ (which is allowed as common vendor
extension). The underscore (_) is not allowed as first character, but later in
the name it is allowed.


I wonder whether the following is valid or not - I think it is not. The
question is whether one can find it in real-world code, where "m" and "m" are
in different translation units (= files).

module m
  type t
  end type t
end module m

subroutine m()
  type t
  end type t
end subroutine m



In principle, I am inclined to close this PR as WONTFIX - and wait for
real-world bug reports. I think the case of comment 0 of having the same-named
polymorphic types in different modules *can* happen in large real-world
programs. But all other examples are a bit artificial. I wonder whether one
should fix the first testcase in this file - as changing the main pattern will
break the ABI. Things like adding further strings could be done later without
breaking the main ABI. (Except the strings get too long for the assemblers.)


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

* [Bug fortran/46313] [OOP] class container naming collisions
  2010-11-05 14:44 [Bug fortran/46313] New: [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue burnus at gcc dot gnu.org
                   ` (11 preceding siblings ...)
  2010-11-09 18:16 ` burnus at gcc dot gnu.org
@ 2010-11-09 18:24 ` burnus at gcc dot gnu.org
  2010-11-09 18:28 ` sgk at troutmask dot apl.washington.edu
                   ` (12 subsequent siblings)
  25 siblings, 0 replies; 27+ messages in thread
From: burnus at gcc dot gnu.org @ 2010-11-09 18:24 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #13 from Tobias Burnus <burnus at gcc dot gnu.org> 2010-11-09 18:24:28 UTC ---
(In reply to comment #11)
> +      char tmp[GFC_MAX_SYMBOL_LEN];
> +      strcpy (&tmp[0], derived->name);
> +         sprintf (string, "%s_%s", ns->proc_name->name, tmp);
> +         strcpy (&tmp[0], string);

That scheme won't work. "tmp" is only GFC_MAX_SYMBOL_LEN long but you keep
adding more and more strings. Currently, you could have:
  <module>_<subroutine>_<internal-sub>_<type>
which has the maximal size of 4*63 + 3 = 255 characters (plus 1 for '\0').

However, GFC_MAX_SYMBOL_LEN is only:
   GFC_MAX_SYMBOL_LEN*2+4 = 63*2+4 = 130 characters

And I do not want so see GFC_MAX_SYMBOL_LEN growing; it is already used at
several places such that it will start to cause memory wastage for large
programs.


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

* [Bug fortran/46313] [OOP] class container naming collisions
  2010-11-05 14:44 [Bug fortran/46313] New: [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue burnus at gcc dot gnu.org
                   ` (12 preceding siblings ...)
  2010-11-09 18:24 ` burnus at gcc dot gnu.org
@ 2010-11-09 18:28 ` sgk at troutmask dot apl.washington.edu
  2010-11-09 18:43 ` burnus at gcc dot gnu.org
                   ` (11 subsequent siblings)
  25 siblings, 0 replies; 27+ messages in thread
From: sgk at troutmask dot apl.washington.edu @ 2010-11-09 18:28 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #14 from Steve Kargl <sgk at troutmask dot apl.washington.edu> 2010-11-09 18:27:49 UTC ---
On Tue, Nov 09, 2010 at 05:59:17PM +0000, janus at gcc dot gnu.org wrote:
> 
> Index: gcc/fortran/class.c
> ===================================================================
> --- gcc/fortran/class.c (revision 166480)
> +++ gcc/fortran/class.c (working copy)
> @@ -117,7 +118,19 @@ get_unique_type_string (char *string, gfc_symbol *
>    if (derived->module)
>      sprintf (string, "%s_%s", derived->module, derived->name);
>    else
> -    sprintf (string, "%s_%s", derived->ns->proc_name->name, derived->name);
> +    {
> +      gfc_namespace *ns;
> +      char tmp[GFC_MAX_SYMBOL_LEN];

GFC_MAX_SYMBOL_LEN is 63.  Is this sufficient space?
Perhaps, snprintf() is needed to prevent buffer overflows
or use of alloca to dynamically size the buffer.  Oh,
the above declaration should probably have the '+1' for
the trailing '\0'.

> +      strcpy (&tmp[0], derived->name);
> +      /* Walk namespace hierarchy.  */
> +      for (ns = derived->ns; ns; ns = ns->parent)
> +       {
> +         sprintf (string, "%s_%s", ns->proc_name->name, tmp);

To solve Tobias' problem, use a capital 'M' (or other capital
letter) for '_'.  gfortran forces everything to lowercase, so
'M' can't appear in a symbol name.


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

* [Bug fortran/46313] [OOP] class container naming collisions
  2010-11-05 14:44 [Bug fortran/46313] New: [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue burnus at gcc dot gnu.org
                   ` (13 preceding siblings ...)
  2010-11-09 18:28 ` sgk at troutmask dot apl.washington.edu
@ 2010-11-09 18:43 ` burnus at gcc dot gnu.org
  2010-12-16  8:37 ` burnus at gcc dot gnu.org
                   ` (10 subsequent siblings)
  25 siblings, 0 replies; 27+ messages in thread
From: burnus at gcc dot gnu.org @ 2010-11-09 18:43 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #15 from Tobias Burnus <burnus at gcc dot gnu.org> 2010-11-09 18:42:52 UTC ---
(In reply to comment #14)
> However, GFC_MAX_SYMBOL_LEN is only:
>    GFC_MAX_SYMBOL_LEN*2+4 = 63*2+4 = 130 characters

Sorry, GFC_MAX_SYMBOL_LEN is only 63 characters. The other was trans.h's
GFC_MAX_MANGLED_SYMBOL_LEN. The symbols defined in gfortran.h have all a length
of "GFC_MAX_SYMBOL_LEN + 1". Thus, if you store the string in a normal
gfc_symbol->name you cannot be longer than 63 characters.

Maybe it is really time to use hashed strings? One could void them for strings
which are shorter and only hash for longer strings (starting with, e.g, a
capital letter to avoid clashes with non-hashed strings).

Note: If you add the symbol __class_%s_%d_a you already have used 13 characters
(for rank > 9) without the "get_unique_type_string" - thus the latter may only
be 50 characters long - that's two times 25 characters, which should be
normally enough. However, I could image automatically generated code, which is
longer. And with further nesting, you really start to have problems. Especially
with submodules, which can be nested infinite times.

Cf. gcc/cp/mangle.c for how C++ mangles the symbols.


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

* [Bug fortran/46313] [OOP] class container naming collisions
  2010-11-05 14:44 [Bug fortran/46313] New: [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue burnus at gcc dot gnu.org
                   ` (14 preceding siblings ...)
  2010-11-09 18:43 ` burnus at gcc dot gnu.org
@ 2010-12-16  8:37 ` burnus at gcc dot gnu.org
  2011-01-02 19:28 ` janus at gcc dot gnu.org
                   ` (9 subsequent siblings)
  25 siblings, 0 replies; 27+ messages in thread
From: burnus at gcc dot gnu.org @ 2010-12-16  8:37 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #16 from Tobias Burnus <burnus at gcc dot gnu.org> 2010-12-16 08:37:16 UTC ---
Cf. also PR 46971


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

* [Bug fortran/46313] [OOP] class container naming collisions
  2010-11-05 14:44 [Bug fortran/46313] New: [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue burnus at gcc dot gnu.org
                   ` (15 preceding siblings ...)
  2010-12-16  8:37 ` burnus at gcc dot gnu.org
@ 2011-01-02 19:28 ` janus at gcc dot gnu.org
  2011-01-07 10:00 ` burnus at gcc dot gnu.org
                   ` (8 subsequent siblings)
  25 siblings, 0 replies; 27+ messages in thread
From: janus at gcc dot gnu.org @ 2011-01-02 19:28 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #17 from janus at gcc dot gnu.org 2011-01-02 19:28:33 UTC ---
(In reply to comment #15)
> Maybe it is really time to use hashed strings? One could void them for strings
> which are shorter and only hash for longer strings (starting with, e.g, a
> capital letter to avoid clashes with non-hashed strings).

This has been implemented as a fix for PR46971.


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

* [Bug fortran/46313] [OOP] class container naming collisions
  2010-11-05 14:44 [Bug fortran/46313] New: [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue burnus at gcc dot gnu.org
                   ` (16 preceding siblings ...)
  2011-01-02 19:28 ` janus at gcc dot gnu.org
@ 2011-01-07 10:00 ` burnus at gcc dot gnu.org
  2011-01-07 12:35 ` janus at gcc dot gnu.org
                   ` (7 subsequent siblings)
  25 siblings, 0 replies; 27+ messages in thread
From: burnus at gcc dot gnu.org @ 2011-01-07 10:00 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #18 from Tobias Burnus <burnus at gcc dot gnu.org> 2011-01-07 09:28:37 UTC ---
(In reply to comment #17)
[...]
> This has been implemented as a fix for PR46971.

Is there any issue left to be fixed? I think there isn't.
(Except for an accepts-invalid diagnostic for comment 7 [module "m" vs.
subroutine "m", which USEs "m"], which is now PR 47203.)

If there is none, I would propose to close this PR as fixed.


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

* [Bug fortran/46313] [OOP] class container naming collisions
  2010-11-05 14:44 [Bug fortran/46313] New: [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue burnus at gcc dot gnu.org
                   ` (17 preceding siblings ...)
  2011-01-07 10:00 ` burnus at gcc dot gnu.org
@ 2011-01-07 12:35 ` janus at gcc dot gnu.org
  2011-01-07 13:02 ` janus at gcc dot gnu.org
                   ` (6 subsequent siblings)
  25 siblings, 0 replies; 27+ messages in thread
From: janus at gcc dot gnu.org @ 2011-01-07 12:35 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #19 from janus at gcc dot gnu.org 2011-01-07 12:16:34 UTC ---
(In reply to comment #18)
> Is there any issue left to be fixed? I think there isn't.
> (Except for an accepts-invalid diagnostic for comment 7 [module "m" vs.
> subroutine "m", which USEs "m"], which is now PR 47203.)

I think the code in comment #12 still does not work. Here is a slightly
modified version:


module one
  type two_three
  end type two_three
end module one

module one_two
  type three
  end type three
end module one_two

use one
use one_two
class(two_three), allocatable :: a1
class(three), allocatable :: a2

print *,allocated(a1)
print *,allocated(a2)

end


In the dump you can see that we end up with one vtab for both types.


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

* [Bug fortran/46313] [OOP] class container naming collisions
  2010-11-05 14:44 [Bug fortran/46313] New: [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue burnus at gcc dot gnu.org
                   ` (18 preceding siblings ...)
  2011-01-07 12:35 ` janus at gcc dot gnu.org
@ 2011-01-07 13:02 ` janus at gcc dot gnu.org
  2011-01-07 14:01 ` burnus at gcc dot gnu.org
                   ` (5 subsequent siblings)
  25 siblings, 0 replies; 27+ messages in thread
From: janus at gcc dot gnu.org @ 2011-01-07 13:02 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #20 from janus at gcc dot gnu.org 2011-01-07 12:58:07 UTC ---
(In reply to comment #19)
> In the dump you can see that we end up with one vtab for both types.

This is easily fixed by putting the first letter of the derived type name in
upper case:


Index: gcc/fortran/class.c
===================================================================
--- gcc/fortran/class.c (revision 168565)
+++ gcc/fortran/class.c (working copy)
@@ -116,13 +116,16 @@

 static void
 get_unique_type_string (char *string, gfc_symbol *derived)
-{  
+{
+  char dt_name[GFC_MAX_SYMBOL_LEN+1];
+  sprintf (dt_name, "%s", derived->name);
+  dt_name[0] = TOUPPER (dt_name[0]);
   if (derived->module)
-    sprintf (string, "%s_%s", derived->module, derived->name);
+    sprintf (string, "%s_%s", derived->module, dt_name);
   else if (derived->ns->proc_name)
-    sprintf (string, "%s_%s", derived->ns->proc_name->name, derived->name);
+    sprintf (string, "%s_%s", derived->ns->proc_name->name, dt_name);
   else
-    sprintf (string, "_%s", derived->name);
+    sprintf (string, "_%s", dt_name);
 }


For a proper runtime test case, one could just add a call to
"same_type_as(a1,a2)" to comment #19.


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

* [Bug fortran/46313] [OOP] class container naming collisions
  2010-11-05 14:44 [Bug fortran/46313] New: [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue burnus at gcc dot gnu.org
                   ` (19 preceding siblings ...)
  2011-01-07 13:02 ` janus at gcc dot gnu.org
@ 2011-01-07 14:01 ` burnus at gcc dot gnu.org
  2011-01-07 14:02 ` burnus at gcc dot gnu.org
                   ` (4 subsequent siblings)
  25 siblings, 0 replies; 27+ messages in thread
From: burnus at gcc dot gnu.org @ 2011-01-07 14:01 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #21 from Tobias Burnus <burnus at gcc dot gnu.org> 2011-01-07 13:25:56 UTC ---
(In reply to comment #19)
> (In reply to comment #18)
> class(two_three), allocatable :: a1
> class(three), allocatable :: a2

> In the dump you can see that we end up with one vtab for both types.

The simplest run-time test is to add:

  print *, same_type_as(a1,a2)

which should always be .FALSE. but is currently .TRUE.


Actually, also something else is odd: One finds in the dump a
            D.1555 = a1._vptr->_hash == a2._vptr->_hash;
even with the patch for PR 41580. However, the check in
gfc_simplify_same_type_as which tests:

+  if ((a->ts.type == BT_CLASS || b->ts.type == BT_CLASS)
+      && !gfc_type_compatible (&a->ts, &b->ts)
+      && !gfc_type_compatible (&b->ts, &a->ts))

should have succeeded as the (declared) type of "a1" is not type compatible to
"a2" - nor vice versa.


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

* [Bug fortran/46313] [OOP] class container naming collisions
  2010-11-05 14:44 [Bug fortran/46313] New: [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue burnus at gcc dot gnu.org
                   ` (20 preceding siblings ...)
  2011-01-07 14:01 ` burnus at gcc dot gnu.org
@ 2011-01-07 14:02 ` burnus at gcc dot gnu.org
  2011-01-09 11:20 ` janus at gcc dot gnu.org
                   ` (3 subsequent siblings)
  25 siblings, 0 replies; 27+ messages in thread
From: burnus at gcc dot gnu.org @ 2011-01-07 14:02 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #22 from Tobias Burnus <burnus at gcc dot gnu.org> 2011-01-07 13:41:17 UTC ---
(In reply to comment #20)
> This is easily fixed by putting the first letter of the derived type name in
> upper case:
[...]

(In reply to comment #21)
> even with the patch for PR 41580. However, the check in
> gfc_simplify_same_type_as [...]
> should have succeeded as the (declared) type of "a1" is not type compatible to
> "a2" - nor vice versa.

Seems to work with the patch from comment 20: The same_type_as is simplified to
.false.

(One could probably still construct ambiguity by making full-use of submodules
types defined in internal functions...)


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

* [Bug fortran/46313] [OOP] class container naming collisions
  2010-11-05 14:44 [Bug fortran/46313] New: [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue burnus at gcc dot gnu.org
                   ` (21 preceding siblings ...)
  2011-01-07 14:02 ` burnus at gcc dot gnu.org
@ 2011-01-09 11:20 ` janus at gcc dot gnu.org
  2011-01-09 11:25 ` janus at gcc dot gnu.org
                   ` (2 subsequent siblings)
  25 siblings, 0 replies; 27+ messages in thread
From: janus at gcc dot gnu.org @ 2011-01-09 11:20 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #23 from janus at gcc dot gnu.org 2011-01-09 10:35:56 UTC ---
Author: janus
Date: Sun Jan  9 10:35:50 2011
New Revision: 168610

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=168610
Log:
2011-01-09  Janus Weil  <janus@gcc.gnu.org>

    PR fortran/46313
    * class.c (get_unique_type_string): Make type name start with upper
    case letter.


2011-01-09  Janus Weil  <janus@gcc.gnu.org>

    PR fortran/46313
    * gfortran.dg/class_35.f90: New.

Added:
    trunk/gcc/testsuite/gfortran.dg/class_35.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/class.c
    trunk/gcc/testsuite/ChangeLog


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

* [Bug fortran/46313] [OOP] class container naming collisions
  2010-11-05 14:44 [Bug fortran/46313] New: [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue burnus at gcc dot gnu.org
                   ` (22 preceding siblings ...)
  2011-01-09 11:20 ` janus at gcc dot gnu.org
@ 2011-01-09 11:25 ` janus at gcc dot gnu.org
  2011-01-09 12:42 ` burnus at gcc dot gnu.org
  2011-09-10  8:41 ` janus at gcc dot gnu.org
  25 siblings, 0 replies; 27+ messages in thread
From: janus at gcc dot gnu.org @ 2011-01-09 11:25 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #24 from janus at gcc dot gnu.org 2011-01-09 10:43:24 UTC ---
r168610 contains the patch from comment #20 which fixes comment #19.

Is there anything left to do here, or should we finally close this one?


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

* [Bug fortran/46313] [OOP] class container naming collisions
  2010-11-05 14:44 [Bug fortran/46313] New: [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue burnus at gcc dot gnu.org
                   ` (23 preceding siblings ...)
  2011-01-09 11:25 ` janus at gcc dot gnu.org
@ 2011-01-09 12:42 ` burnus at gcc dot gnu.org
  2011-09-10  8:41 ` janus at gcc dot gnu.org
  25 siblings, 0 replies; 27+ messages in thread
From: burnus at gcc dot gnu.org @ 2011-01-09 12:42 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #25 from Tobias Burnus <burnus at gcc dot gnu.org> 2011-01-09 12:34:08 UTC ---
(In reply to comment #24)
> r168610 contains the patch from comment #20 which fixes comment #19.
> 
> Is there anything left to do here, or should we finally close this one?

I think we might need to revisit the issue when submodules are implemented -
but until then everything should work - even the program below works - thus
closing as FIXED should be OK.

The following program has a name clash - but as the internal procedure is
internal, it does not leak out into global name space and works:

module mm
type t
end type t
end module mm

subroutine outer
call mm
contains
  subroutine mm
    type t
    end type t
    class(t),allocatable :: a2
    allocate( t :: a2)
  end subroutine mm
end 

use mm
class(t),allocatable :: a1
allocate( t :: a1)
call outer
end


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

* [Bug fortran/46313] [OOP] class container naming collisions
  2010-11-05 14:44 [Bug fortran/46313] New: [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue burnus at gcc dot gnu.org
                   ` (24 preceding siblings ...)
  2011-01-09 12:42 ` burnus at gcc dot gnu.org
@ 2011-09-10  8:41 ` janus at gcc dot gnu.org
  25 siblings, 0 replies; 27+ messages in thread
From: janus at gcc dot gnu.org @ 2011-09-10  8:41 UTC (permalink / raw)
  To: gcc-bugs

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

janus at gcc dot gnu.org changed:

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

--- Comment #26 from janus at gcc dot gnu.org 2011-09-10 08:22:13 UTC ---
(In reply to comment #25)
> > Is there anything left to do here, or should we finally close this one?
> 
> I think we might need to revisit the issue when submodules are implemented -
> but until then everything should work - even the program below works - thus
> closing as FIXED should be OK.

Finally closing as fixed.


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

end of thread, other threads:[~2011-09-10  8:23 UTC | newest]

Thread overview: 27+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2010-11-05 14:44 [Bug fortran/46313] New: [OOP] OOP-ABI issue, ALLOCATE issue, CLASS renaming issue burnus at gcc dot gnu.org
2010-11-05 15:47 ` [Bug fortran/46313] " kargl at gcc dot gnu.org
2010-11-05 16:04 ` sgk at troutmask dot apl.washington.edu
2010-11-06  0:38 ` kargl at gcc dot gnu.org
2010-11-06 15:26 ` janus at gcc dot gnu.org
2010-11-09 10:40 ` janus at gcc dot gnu.org
2010-11-09 11:54 ` janus at gcc dot gnu.org
2010-11-09 12:52 ` [Bug fortran/46313] [OOP] class container naming collisions janus at gcc dot gnu.org
2010-11-09 13:52 ` burnus at gcc dot gnu.org
2010-11-09 16:32 ` janus at gcc dot gnu.org
2010-11-09 17:07 ` janus at gcc dot gnu.org
2010-11-09 17:59 ` janus at gcc dot gnu.org
2010-11-09 18:16 ` burnus at gcc dot gnu.org
2010-11-09 18:24 ` burnus at gcc dot gnu.org
2010-11-09 18:28 ` sgk at troutmask dot apl.washington.edu
2010-11-09 18:43 ` burnus at gcc dot gnu.org
2010-12-16  8:37 ` burnus at gcc dot gnu.org
2011-01-02 19:28 ` janus at gcc dot gnu.org
2011-01-07 10:00 ` burnus at gcc dot gnu.org
2011-01-07 12:35 ` janus at gcc dot gnu.org
2011-01-07 13:02 ` janus at gcc dot gnu.org
2011-01-07 14:01 ` burnus at gcc dot gnu.org
2011-01-07 14:02 ` burnus at gcc dot gnu.org
2011-01-09 11:20 ` janus at gcc dot gnu.org
2011-01-09 11:25 ` janus at gcc dot gnu.org
2011-01-09 12:42 ` burnus at gcc dot gnu.org
2011-09-10  8:41 ` 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).