public inbox for gcc-patches@gcc.gnu.org
 help / color / mirror / Atom feed
* [Patch, fortran] PR81447 - [7/8] gfortran fails to recognize the exact dynamic type of a polymorphic entity that was allocated in a external procedure
@ 2017-11-01 18:22 Paul Richard Thomas
  2017-11-02 20:11 ` Paul Richard Thomas
  0 siblings, 1 reply; 6+ messages in thread
From: Paul Richard Thomas @ 2017-11-01 18:22 UTC (permalink / raw)
  To: gcc-patches, fortran; +Cc: Steve Kargl

[-- Attachment #1: Type: text/plain, Size: 1984 bytes --]

Dear All,

This patch is adequately described by the comment in the second chunk
applied to resolve.c.

Note, however, that the 'unconditionally' is promptly undermined by
the subsequent conditions. I will change the adjective appropriately.
In writing this, I have just realised that access=private need not
have a vtable generated unless it is required for a class within the
module. I will make it so a regtest once more.

Some of the increases in counts in the tree dumps look alarming. They
are however just a reflection of the number of derived types in some
of the tests and are due to the auxiliary vtable functions.

Bootstrapped and regtested on FC23/x86_64 - OK for trunk and then 7- branch?

Paul

2017-11-01  Paul Thomas  <pault@gcc.gnu.org>

    PR fortran/81447
    PR fortran/82783
    * resolve.c (resolve_component): There is no need to resolve
    the components of a use associated vtype.
    (resolve_fl_derived): Unconditionally generate a vtable for any
    module derived type, as long as the standard is F2003 or later
    and it is not a vtype or a PDT template.

2017-11-01  Paul Thomas  <pault@gcc.gnu.org>

    PR fortran/81447
    * gfortran.dg/class_65.f90: New test.
    * gfortran.dg/alloc_comp_basics_1.f90: Increase builtin_free
    count from 18 to 21.
    * gfortran.dg/allocatable_scalar_9.f90: Increase builtin_free
    count from 32 to 54.
    * gfortran.dg/auto_dealloc_1.f90: Increase builtin_free
    count from 4 to 10.
    * gfortran.dg/coarray_lib_realloc_1.f90: Increase builtin_free
    count from 3 to 6. Likewise _gfortran_caf_deregister from 2 to
    3, builtin_malloc from 1 to 4 and builtin_memcpy|= MEM from
    2 to 5.
    * gfortran.dg/finalize_28.f90: Increase builtin_free
    count from 3 to 6.
    * gfortran.dg/move_alloc_15.f90: Increase builtin_free and
    builtin_malloc counts from 11 to 14.
    * gfortran.dg/typebound_proc_27.f03: Increase builtin_free
    count from 7 to 10. Likewise builtin_malloc from 12 to 15.

[-- Attachment #2: submit.diff --]
[-- Type: text/plain, Size: 10737 bytes --]

Index: gcc/fortran/match.c
===================================================================
*** gcc/fortran/match.c	(revision 254300)
--- gcc/fortran/match.c	(working copy)
*************** gfc_match_allocate (void)
*** 4010,4019 ****
  
  	  /* TODO understand why this error does not appear but, instead,
  	     the derived type is caught as a variable in primary.c.  */
! 	  if (gfc_spec_list_type (type_param_spec_list, NULL) != SPEC_EXPLICIT)
  	    {
  	      gfc_error ("The type parameter spec list in the type-spec at "
! 			 "%L cannot contain ASSUMED or DEFERRED parameters",
  			 &old_locus);
  	      goto cleanup;
  	    }
--- 4010,4019 ----
  
  	  /* TODO understand why this error does not appear but, instead,
  	     the derived type is caught as a variable in primary.c.  */
! 	  if (gfc_spec_list_type (type_param_spec_list, NULL) == SPEC_DEFERRED)
  	    {
  	      gfc_error ("The type parameter spec list in the type-spec at "
! 			 "%L cannot contain DEFERRED parameters",
  			 &old_locus);
  	      goto cleanup;
  	    }
Index: gcc/fortran/resolve.c
===================================================================
*** gcc/fortran/resolve.c	(revision 254300)
--- gcc/fortran/resolve.c	(working copy)
*************** resolve_component (gfc_component *c, gfc
*** 13496,13501 ****
--- 13496,13504 ----
    if (c->attr.artificial)
      return true;
  
+   if (sym->attr.vtype && sym->attr.use_assoc)
+     return true;
+ 
    /* F2008, C442.  */
    if ((!sym->attr.is_class || c != sym->components)
        && c->attr.codimension
*************** resolve_fl_derived (gfc_symbol *sym)
*** 14075,14080 ****
--- 14078,14096 ----
    if (!resolve_typebound_procedures (sym))
      return false;
  
+   /* Generate module vtables unconditionally. If this is not done
+      class declarations in external procedures wind up with their
+      own version and so SELECT TYPE fails because the vptrs do not
+      have the same address.  */
+   if (gfc_option.allow_std & GFC_STD_F2003
+       && sym->ns->proc_name
+       && sym->ns->proc_name->attr.flavor == FL_MODULE
+       && !(sym->attr.use_assoc || sym->attr.vtype || sym->attr.pdt_template))
+     {
+       gfc_symbol *vtab = gfc_find_derived_vtab (sym);
+       gfc_set_sym_referenced (vtab);
+     }
+ 
    return true;
  }
  
Index: gcc/testsuite/gfortran.dg/alloc_comp_basics_1.f90
===================================================================
*** gcc/testsuite/gfortran.dg/alloc_comp_basics_1.f90	(revision 254300)
--- gcc/testsuite/gfortran.dg/alloc_comp_basics_1.f90	(working copy)
*************** contains
*** 141,144 ****
      end subroutine check_alloc2
  
  end program alloc
! ! { dg-final { scan-tree-dump-times "builtin_free" 18 "original" } }
--- 141,144 ----
      end subroutine check_alloc2
  
  end program alloc
! ! { dg-final { scan-tree-dump-times "builtin_free" 21 "original" } }
Index: gcc/testsuite/gfortran.dg/allocatable_scalar_9.f90
===================================================================
*** gcc/testsuite/gfortran.dg/allocatable_scalar_9.f90	(revision 254300)
--- gcc/testsuite/gfortran.dg/allocatable_scalar_9.f90	(working copy)
***************
*** 5,17 ****
  !
  ! Contributed by Tobias Burnus <burnus@gcc.gnu.org>
  
! module m                                                                        
! type st                                                                         
!   integer , allocatable :: a1                                                   
! end type st                                                                     
! type at                                                                         
!   integer , allocatable :: a2(:)                                                
! end type at                                                                     
  
  type t1
    type(st), allocatable :: b1
--- 5,17 ----
  !
  ! Contributed by Tobias Burnus <burnus@gcc.gnu.org>
  
! module m
! type st
!   integer , allocatable :: a1
! end type st
! type at
!   integer , allocatable :: a2(:)
! end type at
  
  type t1
    type(st), allocatable :: b1
*************** if(allocated(na4%b4)) call abort()
*** 52,55 ****
  end block
  end
  
! ! { dg-final { scan-tree-dump-times "__builtin_free" 32 "original" } }
--- 52,55 ----
  end block
  end
  
! ! { dg-final { scan-tree-dump-times "__builtin_free" 54 "original" } }
Index: gcc/testsuite/gfortran.dg/auto_dealloc_1.f90
===================================================================
*** gcc/testsuite/gfortran.dg/auto_dealloc_1.f90	(revision 254300)
--- gcc/testsuite/gfortran.dg/auto_dealloc_1.f90	(working copy)
*************** contains
*** 50,56 ****
      m%k%i = 45
    end subroutine
  
! end module 
  
  
! ! { dg-final { scan-tree-dump-times "__builtin_free" 4 "original" } }
--- 50,56 ----
      m%k%i = 45
    end subroutine
  
! end module
  
  
! ! { dg-final { scan-tree-dump-times "__builtin_free" 10 "original" } }
Index: gcc/testsuite/gfortran.dg/class_65.f90
===================================================================
*** gcc/testsuite/gfortran.dg/class_65.f90	(nonexistent)
--- gcc/testsuite/gfortran.dg/class_65.f90	(working copy)
***************
*** 0 ****
--- 1,41 ----
+ ! { dg-do run }
+ !
+ ! Test the fix for PR81447 in which a vtable was not being created
+ ! in the module 'm' so that x->vptr in 's' did not have the same
+ ! value as that in 'p'.
+ !
+ ! Contributed by Mat Cross  <mathewc@nag.co.uk>
+ !
+ Module m
+   Type :: t
+     integer :: i
+   End Type
+ End Module
+ 
+ Program p
+   Use m
+   Class (t), Allocatable :: x
+   Interface
+     Subroutine s(x)
+       Use m
+       Class (t), Allocatable :: x
+     End Subroutine
+   End Interface
+   Call s(x)
+   Select Type (x)
+   Type Is (t)
+     Continue
+   Class Is (t)
+     call abort
+   Class Default
+     call abort
+   End Select
+ !  Print *, 'ok'
+ End Program
+ 
+ Subroutine s(x)
+   Use m, Only: t
+   Implicit None
+   Class (t), Allocatable :: x
+   Allocate (t :: x)
+ End Subroutine
Index: gcc/testsuite/gfortran.dg/coarray_lib_realloc_1.f90
===================================================================
*** gcc/testsuite/gfortran.dg/coarray_lib_realloc_1.f90	(revision 254300)
--- gcc/testsuite/gfortran.dg/coarray_lib_realloc_1.f90	(working copy)
*************** x = y
*** 21,34 ****
  end
  
  ! For comp%ii: End of scope of x + y (2x) and for the LHS of the assignment (1x)
! ! { dg-final { scan-tree-dump-times "__builtin_free" 3 "original" } }
  
  ! For comp%CAF:  End of scope of x + y (2x); no LHS freeing for the CAF in assignment
! ! { dg-final { scan-tree-dump-times "_gfortran_caf_deregister" 2 "original" } }
  
  ! Only malloc "ii":
! ! { dg-final { scan-tree-dump-times "__builtin_malloc" 1 "original" } }
  
  ! But copy "ii" and "CAF":
! ! { dg-final { scan-tree-dump-times "__builtin_memcpy|= MEM" 2 "original" } }
  
--- 21,34 ----
  end
  
  ! For comp%ii: End of scope of x + y (2x) and for the LHS of the assignment (1x)
! ! { dg-final { scan-tree-dump-times "__builtin_free" 6 "original" } }
  
  ! For comp%CAF:  End of scope of x + y (2x); no LHS freeing for the CAF in assignment
! ! { dg-final { scan-tree-dump-times "_gfortran_caf_deregister" 3 "original" } }
  
  ! Only malloc "ii":
! ! { dg-final { scan-tree-dump-times "__builtin_malloc" 4 "original" } }
  
  ! But copy "ii" and "CAF":
! ! { dg-final { scan-tree-dump-times "__builtin_memcpy|= MEM" 5 "original" } }
  
Index: gcc/testsuite/gfortran.dg/finalize_28.f90
===================================================================
*** gcc/testsuite/gfortran.dg/finalize_28.f90	(revision 254300)
--- gcc/testsuite/gfortran.dg/finalize_28.f90	(working copy)
*************** contains
*** 21,24 ****
      integer, intent(out) :: edges(:,:)
    end subroutine coo_dump_edges
  end module coo_graphs
! ! { dg-final { scan-tree-dump-times "__builtin_free" 3 "original" } }
--- 21,24 ----
      integer, intent(out) :: edges(:,:)
    end subroutine coo_dump_edges
  end module coo_graphs
! ! { dg-final { scan-tree-dump-times "__builtin_free" 6 "original" } }
Index: gcc/testsuite/gfortran.dg/move_alloc_15.f90
===================================================================
*** gcc/testsuite/gfortran.dg/move_alloc_15.f90	(revision 254300)
--- gcc/testsuite/gfortran.dg/move_alloc_15.f90	(working copy)
*************** contains
*** 84,88 ****
      end do
    end subroutine
  end program name
! ! { dg-final { scan-tree-dump-times "__builtin_malloc" 11 "original" } }
! ! { dg-final { scan-tree-dump-times "__builtin_free" 11 "original" } }
--- 84,88 ----
      end do
    end subroutine
  end program name
! ! { dg-final { scan-tree-dump-times "__builtin_malloc" 14 "original" } }
! ! { dg-final { scan-tree-dump-times "__builtin_free" 14 "original" } }
Index: gcc/testsuite/gfortran.dg/typebound_proc_27.f03
===================================================================
*** gcc/testsuite/gfortran.dg/typebound_proc_27.f03	(revision 254300)
--- gcc/testsuite/gfortran.dg/typebound_proc_27.f03	(working copy)
***************
*** 1,6 ****
  ! { dg-do run }
  ! { dg-options "-fdump-tree-original" }
! ! 
  ! PR fortran/47586
  ! Missing deep copy for data pointer returning functions when the type
  ! has allocatable components
--- 1,6 ----
  ! { dg-do run }
  ! { dg-options "-fdump-tree-original" }
! !
  ! PR fortran/47586
  ! Missing deep copy for data pointer returning functions when the type
  ! has allocatable components
*************** end program prog
*** 77,91 ****
  ! statements.
  ! It is assumed that if the number of allocate is right, the number of
  ! deep copies is right too.
! ! { dg-final { scan-tree-dump-times "__builtin_malloc" 12 "original" } }
  
  !
  ! Realloc are only used for assignments to `that%i'.  Don't know why.
  ! { dg-final { scan-tree-dump-times "__builtin_realloc" 6 "original" } }
! ! 
  
  ! No leak: Only assignments to `this' use malloc.  Assignments to `that%i'
  ! take the realloc path after the first assignment, so don't count as a malloc.
! ! { dg-final { scan-tree-dump-times "__builtin_free" 7 "original" } }
  !
  
--- 77,91 ----
  ! statements.
  ! It is assumed that if the number of allocate is right, the number of
  ! deep copies is right too.
! ! { dg-final { scan-tree-dump-times "__builtin_malloc" 15 "original" } }
  
  !
  ! Realloc are only used for assignments to `that%i'.  Don't know why.
  ! { dg-final { scan-tree-dump-times "__builtin_realloc" 6 "original" } }
! !
  
  ! No leak: Only assignments to `this' use malloc.  Assignments to `that%i'
  ! take the realloc path after the first assignment, so don't count as a malloc.
! ! { dg-final { scan-tree-dump-times "__builtin_free" 10 "original" } }
  !
  

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

* Re: [Patch, fortran] PR81447 - [7/8] gfortran fails to recognize the exact dynamic type of a polymorphic entity that was allocated in a external procedure
  2017-11-01 18:22 [Patch, fortran] PR81447 - [7/8] gfortran fails to recognize the exact dynamic type of a polymorphic entity that was allocated in a external procedure Paul Richard Thomas
@ 2017-11-02 20:11 ` Paul Richard Thomas
  2017-11-04 18:03   ` Andre Vehreschild
  0 siblings, 1 reply; 6+ messages in thread
From: Paul Richard Thomas @ 2017-11-02 20:11 UTC (permalink / raw)
  To: gcc-patches, fortran; +Cc: Steve Kargl

[-- Attachment #1: Type: text/plain, Size: 2395 bytes --]

Dear All,

Please find attached the revised version of the patch following my
late realizations in yesterday's submission.

Cheers

Paul


On 1 November 2017 at 18:22, Paul Richard Thomas
<paul.richard.thomas@gmail.com> wrote:
> Dear All,
>
> This patch is adequately described by the comment in the second chunk
> applied to resolve.c.
>
> Note, however, that the 'unconditionally' is promptly undermined by
> the subsequent conditions. I will change the adjective appropriately.
> In writing this, I have just realised that access=private need not
> have a vtable generated unless it is required for a class within the
> module. I will make it so a regtest once more.
>
> Some of the increases in counts in the tree dumps look alarming. They
> are however just a reflection of the number of derived types in some
> of the tests and are due to the auxiliary vtable functions.
>
> Bootstrapped and regtested on FC23/x86_64 - OK for trunk and then 7- branch?
>
> Paul
>
> 2017-11-01  Paul Thomas  <pault@gcc.gnu.org>
>
>     PR fortran/81447
>     PR fortran/82783
>     * resolve.c (resolve_component): There is no need to resolve
>     the components of a use associated vtype.
>     (resolve_fl_derived): Unconditionally generate a vtable for any
>     module derived type, as long as the standard is F2003 or later
>     and it is not a vtype or a PDT template.
>
> 2017-11-01  Paul Thomas  <pault@gcc.gnu.org>
>
>     PR fortran/81447
>     * gfortran.dg/class_65.f90: New test.
>     * gfortran.dg/alloc_comp_basics_1.f90: Increase builtin_free
>     count from 18 to 21.
>     * gfortran.dg/allocatable_scalar_9.f90: Increase builtin_free
>     count from 32 to 54.
>     * gfortran.dg/auto_dealloc_1.f90: Increase builtin_free
>     count from 4 to 10.
>     * gfortran.dg/coarray_lib_realloc_1.f90: Increase builtin_free
>     count from 3 to 6. Likewise _gfortran_caf_deregister from 2 to
>     3, builtin_malloc from 1 to 4 and builtin_memcpy|= MEM from
>     2 to 5.
>     * gfortran.dg/finalize_28.f90: Increase builtin_free
>     count from 3 to 6.
>     * gfortran.dg/move_alloc_15.f90: Increase builtin_free and
>     builtin_malloc counts from 11 to 14.
>     * gfortran.dg/typebound_proc_27.f03: Increase builtin_free
>     count from 7 to 10. Likewise builtin_malloc from 12 to 15.



-- 
"If you can't explain it simply, you don't understand it well enough"
- Albert Einstein

[-- Attachment #2: resubmit.diff --]
[-- Type: text/plain, Size: 9262 bytes --]

Index: gcc/fortran/resolve.c
===================================================================
*** gcc/fortran/resolve.c	(revision 254300)
--- gcc/fortran/resolve.c	(working copy)
*************** resolve_component (gfc_component *c, gfc
*** 13496,13501 ****
--- 13496,13504 ----
    if (c->attr.artificial)
      return true;

+   if (sym->attr.vtype && sym->attr.use_assoc)
+     return true;
+
    /* F2008, C442.  */
    if ((!sym->attr.is_class || c != sym->components)
        && c->attr.codimension
*************** resolve_fl_derived (gfc_symbol *sym)
*** 14075,14080 ****
--- 14078,14097 ----
    if (!resolve_typebound_procedures (sym))
      return false;

+   /* Generate module vtables subject to their accessibility and their not
+      being vtables or pdt templates. If this is not done class declarations
+      in external procedures wind up with their own version and so SELECT TYPE
+      fails because the vptrs do not have the same address.  */
+   if (gfc_option.allow_std & GFC_STD_F2003
+       && sym->ns->proc_name
+       && sym->ns->proc_name->attr.flavor == FL_MODULE
+       && sym->attr.access != ACCESS_PRIVATE
+       && !(sym->attr.use_assoc || sym->attr.vtype || sym->attr.pdt_template))
+     {
+       gfc_symbol *vtab = gfc_find_derived_vtab (sym);
+       gfc_set_sym_referenced (vtab);
+     }
+
    return true;
  }

Index: gcc/testsuite/gfortran.dg/alloc_comp_basics_1.f90
===================================================================
*** gcc/testsuite/gfortran.dg/alloc_comp_basics_1.f90	(revision 254300)
--- gcc/testsuite/gfortran.dg/alloc_comp_basics_1.f90	(working copy)
*************** contains
*** 141,144 ****
      end subroutine check_alloc2

  end program alloc
! ! { dg-final { scan-tree-dump-times "builtin_free" 18 "original" } }
--- 141,144 ----
      end subroutine check_alloc2

  end program alloc
! ! { dg-final { scan-tree-dump-times "builtin_free" 21 "original" } }
Index: gcc/testsuite/gfortran.dg/allocatable_scalar_9.f90
===================================================================
*** gcc/testsuite/gfortran.dg/allocatable_scalar_9.f90	(revision 254300)
--- gcc/testsuite/gfortran.dg/allocatable_scalar_9.f90	(working copy)
***************
*** 5,17 ****
  !
  ! Contributed by Tobias Burnus <burnus@gcc.gnu.org>

! module m
! type st
!   integer , allocatable :: a1
! end type st
! type at
!   integer , allocatable :: a2(:)
! end type at

  type t1
    type(st), allocatable :: b1
--- 5,17 ----
  !
  ! Contributed by Tobias Burnus <burnus@gcc.gnu.org>

! module m
! type st
!   integer , allocatable :: a1
! end type st
! type at
!   integer , allocatable :: a2(:)
! end type at

  type t1
    type(st), allocatable :: b1
*************** if(allocated(na4%b4)) call abort()
*** 52,55 ****
  end block
  end

! ! { dg-final { scan-tree-dump-times "__builtin_free" 32 "original" } }
--- 52,55 ----
  end block
  end

! ! { dg-final { scan-tree-dump-times "__builtin_free" 54 "original" } }
Index: gcc/testsuite/gfortran.dg/auto_dealloc_1.f90
===================================================================
*** gcc/testsuite/gfortran.dg/auto_dealloc_1.f90	(revision 254300)
--- gcc/testsuite/gfortran.dg/auto_dealloc_1.f90	(working copy)
*************** contains
*** 50,56 ****
      m%k%i = 45
    end subroutine

! end module


! ! { dg-final { scan-tree-dump-times "__builtin_free" 4 "original" } }
--- 50,56 ----
      m%k%i = 45
    end subroutine

! end module


! ! { dg-final { scan-tree-dump-times "__builtin_free" 10 "original" } }
Index: gcc/testsuite/gfortran.dg/class_65.f90
===================================================================
*** gcc/testsuite/gfortran.dg/class_65.f90	(nonexistent)
--- gcc/testsuite/gfortran.dg/class_65.f90	(working copy)
***************
*** 0 ****
--- 1,41 ----
+ ! { dg-do run }
+ !
+ ! Test the fix for PR81447 in which a vtable was not being created
+ ! in the module 'm' so that x->vptr in 's' did not have the same
+ ! value as that in 'p'.
+ !
+ ! Contributed by Mat Cross  <mathewc@nag.co.uk>
+ !
+ Module m
+   Type :: t
+     integer :: i
+   End Type
+ End Module
+
+ Program p
+   Use m
+   Class (t), Allocatable :: x
+   Interface
+     Subroutine s(x)
+       Use m
+       Class (t), Allocatable :: x
+     End Subroutine
+   End Interface
+   Call s(x)
+   Select Type (x)
+   Type Is (t)
+     Continue
+   Class Is (t)
+     call abort
+   Class Default
+     call abort
+   End Select
+ !  Print *, 'ok'
+ End Program
+
+ Subroutine s(x)
+   Use m, Only: t
+   Implicit None
+   Class (t), Allocatable :: x
+   Allocate (t :: x)
+ End Subroutine
Index: gcc/testsuite/gfortran.dg/coarray_lib_realloc_1.f90
===================================================================
*** gcc/testsuite/gfortran.dg/coarray_lib_realloc_1.f90	(revision 254300)
--- gcc/testsuite/gfortran.dg/coarray_lib_realloc_1.f90	(working copy)
*************** x = y
*** 21,34 ****
  end

  ! For comp%ii: End of scope of x + y (2x) and for the LHS of the assignment (1x)
! ! { dg-final { scan-tree-dump-times "__builtin_free" 3 "original" } }

  ! For comp%CAF:  End of scope of x + y (2x); no LHS freeing for the CAF in assignment
! ! { dg-final { scan-tree-dump-times "_gfortran_caf_deregister" 2 "original" } }

  ! Only malloc "ii":
! ! { dg-final { scan-tree-dump-times "__builtin_malloc" 1 "original" } }

  ! But copy "ii" and "CAF":
! ! { dg-final { scan-tree-dump-times "__builtin_memcpy|= MEM" 2 "original" } }

--- 21,34 ----
  end

  ! For comp%ii: End of scope of x + y (2x) and for the LHS of the assignment (1x)
! ! { dg-final { scan-tree-dump-times "__builtin_free" 6 "original" } }

  ! For comp%CAF:  End of scope of x + y (2x); no LHS freeing for the CAF in assignment
! ! { dg-final { scan-tree-dump-times "_gfortran_caf_deregister" 3 "original" } }

  ! Only malloc "ii":
! ! { dg-final { scan-tree-dump-times "__builtin_malloc" 4 "original" } }

  ! But copy "ii" and "CAF":
! ! { dg-final { scan-tree-dump-times "__builtin_memcpy|= MEM" 5 "original" } }

Index: gcc/testsuite/gfortran.dg/finalize_28.f90
===================================================================
*** gcc/testsuite/gfortran.dg/finalize_28.f90	(revision 254300)
--- gcc/testsuite/gfortran.dg/finalize_28.f90	(working copy)
*************** contains
*** 21,24 ****
      integer, intent(out) :: edges(:,:)
    end subroutine coo_dump_edges
  end module coo_graphs
! ! { dg-final { scan-tree-dump-times "__builtin_free" 3 "original" } }
--- 21,24 ----
      integer, intent(out) :: edges(:,:)
    end subroutine coo_dump_edges
  end module coo_graphs
! ! { dg-final { scan-tree-dump-times "__builtin_free" 6 "original" } }
Index: gcc/testsuite/gfortran.dg/move_alloc_15.f90
===================================================================
*** gcc/testsuite/gfortran.dg/move_alloc_15.f90	(revision 254300)
--- gcc/testsuite/gfortran.dg/move_alloc_15.f90	(working copy)
*************** contains
*** 84,88 ****
      end do
    end subroutine
  end program name
! ! { dg-final { scan-tree-dump-times "__builtin_malloc" 11 "original" } }
! ! { dg-final { scan-tree-dump-times "__builtin_free" 11 "original" } }
--- 84,88 ----
      end do
    end subroutine
  end program name
! ! { dg-final { scan-tree-dump-times "__builtin_malloc" 14 "original" } }
! ! { dg-final { scan-tree-dump-times "__builtin_free" 14 "original" } }
Index: gcc/testsuite/gfortran.dg/typebound_proc_27.f03
===================================================================
*** gcc/testsuite/gfortran.dg/typebound_proc_27.f03	(revision 254300)
--- gcc/testsuite/gfortran.dg/typebound_proc_27.f03	(working copy)
***************
*** 1,6 ****
  ! { dg-do run }
  ! { dg-options "-fdump-tree-original" }
! !
  ! PR fortran/47586
  ! Missing deep copy for data pointer returning functions when the type
  ! has allocatable components
--- 1,6 ----
  ! { dg-do run }
  ! { dg-options "-fdump-tree-original" }
! !
  ! PR fortran/47586
  ! Missing deep copy for data pointer returning functions when the type
  ! has allocatable components
*************** end program prog
*** 77,91 ****
  ! statements.
  ! It is assumed that if the number of allocate is right, the number of
  ! deep copies is right too.
! ! { dg-final { scan-tree-dump-times "__builtin_malloc" 12 "original" } }

  !
  ! Realloc are only used for assignments to `that%i'.  Don't know why.
  ! { dg-final { scan-tree-dump-times "__builtin_realloc" 6 "original" } }
! !

  ! No leak: Only assignments to `this' use malloc.  Assignments to `that%i'
  ! take the realloc path after the first assignment, so don't count as a malloc.
! ! { dg-final { scan-tree-dump-times "__builtin_free" 7 "original" } }
  !

--- 77,91 ----
  ! statements.
  ! It is assumed that if the number of allocate is right, the number of
  ! deep copies is right too.
! ! { dg-final { scan-tree-dump-times "__builtin_malloc" 15 "original" } }

  !
  ! Realloc are only used for assignments to `that%i'.  Don't know why.
  ! { dg-final { scan-tree-dump-times "__builtin_realloc" 6 "original" } }
! !

  ! No leak: Only assignments to `this' use malloc.  Assignments to `that%i'
  ! take the realloc path after the first assignment, so don't count as a malloc.
! ! { dg-final { scan-tree-dump-times "__builtin_free" 10 "original" } }
  !


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

* Re: [Patch, fortran] PR81447 - [7/8] gfortran fails to recognize the exact dynamic type of a polymorphic entity that was allocated in a external procedure
  2017-11-02 20:11 ` Paul Richard Thomas
@ 2017-11-04 18:03   ` Andre Vehreschild
  2017-11-04 18:35     ` Thomas Koenig
  0 siblings, 1 reply; 6+ messages in thread
From: Andre Vehreschild @ 2017-11-04 18:03 UTC (permalink / raw)
  To: Paul Richard Thomas; +Cc: gcc-patches, fortran, Steve Kargl

Hi Paul,

On Thu, 2 Nov 2017 20:11:29 +0000
Paul Richard Thomas <paul.richard.thomas@gmail.com> wrote:

> *************** resolve_fl_derived (gfc_symbol *sym)
> *** 14075,14080 ****
> --- 14078,14097 ----
>     if (!resolve_typebound_procedures (sym))
>       return false;
> 
> +   /* Generate module vtables subject to their accessibility and their not
> +      being vtables or pdt templates. If this is not done class declarations
> +      in external procedures wind up with their own version and so SELECT
> TYPE
> +      fails because the vptrs do not have the same address.  */
> +   if (gfc_option.allow_std & GFC_STD_F2003

Shouldn't that better be

   if ((gfc_option.allow_std & GFC_STD_F2003) > 0

? I regularly fall on my nose because of the compiler binding this not as
expected. 

> +       && sym->ns->proc_name
> +       && sym->ns->proc_name->attr.flavor == FL_MODULE
> +       && sym->attr.access != ACCESS_PRIVATE
> +       && !(sym->attr.use_assoc || sym->attr.vtype ||
> sym->attr.pdt_template))
> +     {
> +       gfc_symbol *vtab = gfc_find_derived_vtab (sym);
> +       gfc_set_sym_referenced (vtab);
> +     }
> +
>     return true;
>   }

Besides that I think this is OK.

Regards,
	Andre
-- 
Andre Vehreschild * Email: vehre ad gmx dot de 

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

* Re: [Patch, fortran] PR81447 - [7/8] gfortran fails to recognize the exact dynamic type of a polymorphic entity that was allocated in a external procedure
  2017-11-04 18:03   ` Andre Vehreschild
@ 2017-11-04 18:35     ` Thomas Koenig
  2017-11-05 12:44       ` Paul Richard Thomas
  0 siblings, 1 reply; 6+ messages in thread
From: Thomas Koenig @ 2017-11-04 18:35 UTC (permalink / raw)
  To: Andre Vehreschild, Paul Richard Thomas; +Cc: gcc-patches, fortran, Steve Kargl

Hi Andre,

> Shouldn't that better be
> 
>     if ((gfc_option.allow_std & GFC_STD_F2003) > 0

I think that

if ((gfc_option.allow_std & GFC_STD_F2003)

would be better - the allow_std field is signed, and
things could get hariy if we ever have close to 32
standards we would like to support.

Hm, come to think of it, is there a special reason to keep
this signed, or could we just change it to unsigned?

Regards

	Thomas

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

* Re: [Patch, fortran] PR81447 - [7/8] gfortran fails to recognize the exact dynamic type of a polymorphic entity that was allocated in a external procedure
  2017-11-04 18:35     ` Thomas Koenig
@ 2017-11-05 12:44       ` Paul Richard Thomas
  2017-11-05 16:57         ` Paul Richard Thomas
  0 siblings, 1 reply; 6+ messages in thread
From: Paul Richard Thomas @ 2017-11-05 12:44 UTC (permalink / raw)
  To: Thomas Koenig; +Cc: Andre Vehreschild, gcc-patches, fortran, Steve Kargl

Hi Andre and Thomas,

Thanks for looking at this.

I left the condition as it is because it is the same practice as all
sorts of other parts of gfortran. That said, Thomas's suggestion is I
think the right one.

Committed revision as revision 254427. 7-branch will come later.

Regards

Paul

On 4 November 2017 at 18:35, Thomas Koenig <tkoenig@netcologne.de> wrote:
> Hi Andre,
>
>> Shouldn't that better be
>>
>>     if ((gfc_option.allow_std & GFC_STD_F2003) > 0
>
>
> I think that
>
> if ((gfc_option.allow_std & GFC_STD_F2003)
>
> would be better - the allow_std field is signed, and
> things could get hariy if we ever have close to 32
> standards we would like to support.
>
> Hm, come to think of it, is there a special reason to keep
> this signed, or could we just change it to unsigned?
>
> Regards
>
>         Thomas



-- 
"If you can't explain it simply, you don't understand it well enough"
- Albert Einstein

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

* Re: [Patch, fortran] PR81447 - [7/8] gfortran fails to recognize the exact dynamic type of a polymorphic entity that was allocated in a external procedure
  2017-11-05 12:44       ` Paul Richard Thomas
@ 2017-11-05 16:57         ` Paul Richard Thomas
  0 siblings, 0 replies; 6+ messages in thread
From: Paul Richard Thomas @ 2017-11-05 16:57 UTC (permalink / raw)
  To: Thomas Koenig; +Cc: Andre Vehreschild, gcc-patches, fortran, Steve Kargl

Committed to 7-branch as revision 254429.


Paul

On 5 November 2017 at 12:44, Paul Richard Thomas
<paul.richard.thomas@gmail.com> wrote:
> Hi Andre and Thomas,
>
> Thanks for looking at this.
>
> I left the condition as it is because it is the same practice as all
> sorts of other parts of gfortran. That said, Thomas's suggestion is I
> think the right one.
>
> Committed revision as revision 254427. 7-branch will come later.
>
> Regards
>
> Paul
>
> On 4 November 2017 at 18:35, Thomas Koenig <tkoenig@netcologne.de> wrote:
>> Hi Andre,
>>
>>> Shouldn't that better be
>>>
>>>     if ((gfc_option.allow_std & GFC_STD_F2003) > 0
>>
>>
>> I think that
>>
>> if ((gfc_option.allow_std & GFC_STD_F2003)
>>
>> would be better - the allow_std field is signed, and
>> things could get hariy if we ever have close to 32
>> standards we would like to support.
>>
>> Hm, come to think of it, is there a special reason to keep
>> this signed, or could we just change it to unsigned?
>>
>> Regards
>>
>>         Thomas
>
>
>
> --
> "If you can't explain it simply, you don't understand it well enough"
> - Albert Einstein



-- 
"If you can't explain it simply, you don't understand it well enough"
- Albert Einstein

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

end of thread, other threads:[~2017-11-05 16:57 UTC | newest]

Thread overview: 6+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2017-11-01 18:22 [Patch, fortran] PR81447 - [7/8] gfortran fails to recognize the exact dynamic type of a polymorphic entity that was allocated in a external procedure Paul Richard Thomas
2017-11-02 20:11 ` Paul Richard Thomas
2017-11-04 18:03   ` Andre Vehreschild
2017-11-04 18:35     ` Thomas Koenig
2017-11-05 12:44       ` Paul Richard Thomas
2017-11-05 16:57         ` Paul Richard Thomas

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