public inbox for gcc-patches@gcc.gnu.org
 help / color / mirror / Atom feed
* [Patch, fortran] PR33986 - ICE on allocatable function result
@ 2007-11-14 10:55 Paul Richard Thomas
  2007-11-14 11:17 ` Paul Richard Thomas
  0 siblings, 1 reply; 4+ messages in thread
From: Paul Richard Thomas @ 2007-11-14 10:55 UTC (permalink / raw)
  To: gcc-patches, fortran

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

:ADDPATCH fortran:

This is another self-explanatory patch, where allocatable function
results were just plain forgotten.

Boostrapped and regtested on x86_ia64 - OK for trunk?

Paul

-- 
The knack of flying is learning how to throw yourself at the ground and miss.
       --Hitchhikers Guide to the Galaxy

[-- Attachment #2: commit.msg --]
[-- Type: application/octet-stream, Size: 265 bytes --]

2007-11-14  Paul Thomas  <pault@gcc.gnu.org>

	PR fortran/33986
	* trans-array.c (gfc_conv_array_parameter): Treat allocatable
	function results.

2007-11-14  Paul Thomas  <pault@gcc.gnu.org>

	PR fortran/333986
	* gfortran.dg/allocatable_function_3.f90: New test.

[-- Warning: decoded text below may be mangled, UTF-8 assumed --]
[-- Attachment #3: submit.diff --]
[-- Type: text/x-patch; name=submit.diff, Size: 3778 bytes --]

Index: /svn/trunk/gcc/testsuite/gfortran.dg/interface_assignment_3.f90
===================================================================
*** /svn/trunk/gcc/testsuite/gfortran.dg/interface_assignment_3.f90	(revision 0)
--- /svn/trunk/gcc/testsuite/gfortran.dg/interface_assignment_3.f90	(revision 0)
***************
*** 0 ****
--- 1,49 ----
+ ! { dg-do compile }
+ ! Checks the fix for PR34008, in which INTENT(INOUT) was disallowed
+ ! for the first argument of assign_m, whereas both INOUT and OUT
+ ! should be allowed.
+ !
+ ! Contributed by Harald Anlauf <anlauf@gmx.de> 
+ !
+ module mo_memory
+   implicit none
+   type t_mi
+      logical       :: alloc = .false.
+   end type t_mi
+   type t_m
+      type(t_mi)    :: i                         ! meta data
+      real, pointer :: ptr (:,:,:,:) => NULL ()
+   end type t_m
+ 
+   interface assignment (=)
+      module  procedure assign_m
+   end interface
+ contains
+   elemental subroutine assign_m (y, x)
+     !---------------------------------------
+     ! overwrite intrinsic assignment routine
+     !---------------------------------------
+     type (t_m), intent(inout) :: y
+     type (t_m), intent(in)    :: x
+     y% i = x% i
+     if (y% i% alloc) y% ptr = x% ptr
+   end subroutine assign_m
+ end module mo_memory
+ 
+ module gfcbug74
+   use mo_memory, only: t_m, assignment (=)
+   implicit none
+   type t_atm
+      type(t_m) :: m(42)
+   end type t_atm
+ contains
+   subroutine assign_atm_to_atm (y, x)
+     type (t_atm), intent(inout) :: y
+     type (t_atm), intent(in)    :: x
+     integer :: i
+ !   do i=1,42; y% m(i) = x% m(i); end do    ! Works
+     y% m = x% m                             ! ICE
+   end subroutine assign_atm_to_atm
+ end module gfcbug74
+ ! { dg-final { cleanup-modules "mo_memory gfcbug74" } }
+ 
Index: /svn/trunk/gcc/fortran/trans-stmt.c
===================================================================
*** /svn/trunk/gcc/fortran/trans-stmt.c	(revision 130157)
--- /svn/trunk/gcc/fortran/trans-stmt.c	(working copy)
*************** gfc_conv_elemental_dependencies (gfc_se 
*** 246,253 ****
        fsym = formal ? formal->sym : NULL;
        if (e->expr_type == EXPR_VARIABLE
  	    && e->rank && fsym
! 	    && fsym->attr.intent == INTENT_OUT
! 	    && gfc_check_fncall_dependency (e, INTENT_OUT, sym, arg0))
  	{
  	  /* Make a local loopinfo for the temporary creation, so that
  	     none of the other ss->info's have to be renormalized.  */
--- 246,254 ----
        fsym = formal ? formal->sym : NULL;
        if (e->expr_type == EXPR_VARIABLE
  	    && e->rank && fsym
! 	    && fsym->attr.intent != INTENT_IN
! 	    && gfc_check_fncall_dependency (e, fsym->attr.intent,
! 					    sym, arg0))
  	{
  	  /* Make a local loopinfo for the temporary creation, so that
  	     none of the other ss->info's have to be renormalized.  */
*************** gfc_trans_call (gfc_code * code, bool de
*** 380,393 ****
        gfc_copy_loopinfo_to_se (&loopse, &loop);
        loopse.ss = ss;
  
!       /* For operator assignment, we need to do dependency checking.  
! 	 We also check the intent of the parameters.  */
        if (dependency_check)
  	{
  	  gfc_symbol *sym;
  	  sym = code->resolved_sym;
- 	  gcc_assert (sym->formal->sym->attr.intent == INTENT_OUT);
- 	  gcc_assert (sym->formal->next->sym->attr.intent == INTENT_IN);
  	  gfc_conv_elemental_dependencies (&se, &loopse, sym,
  					   code->ext.actual);
  	}
--- 381,391 ----
        gfc_copy_loopinfo_to_se (&loopse, &loop);
        loopse.ss = ss;
  
!       /* For operator assignment, do dependency checking.  */
        if (dependency_check)
  	{
  	  gfc_symbol *sym;
  	  sym = code->resolved_sym;
  	  gfc_conv_elemental_dependencies (&se, &loopse, sym,
  					   code->ext.actual);
  	}

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

* Re: [Patch, fortran] PR33986 - ICE on allocatable function result
  2007-11-14 10:55 [Patch, fortran] PR33986 - ICE on allocatable function result Paul Richard Thomas
@ 2007-11-14 11:17 ` Paul Richard Thomas
  2007-11-14 15:15   ` Tobias Burnus
  2007-11-14 17:02   ` Jerry DeLisle
  0 siblings, 2 replies; 4+ messages in thread
From: Paul Richard Thomas @ 2007-11-14 11:17 UTC (permalink / raw)
  To: gcc-patches, fortran

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

Sorry, I addeddd the previous patch - herewith the correct one.

Paul
>
-- 
The knack of flying is learning how to throw yourself at the ground and miss.
       --Hitchhikers Guide to the Galaxy

[-- Warning: decoded text below may be mangled, UTF-8 assumed --]
[-- Attachment #2: submit.diff --]
[-- Type: text/x-patch; name=submit.diff, Size: 1827 bytes --]

Index: /svn/trunk/gcc/testsuite/gfortran.dg/allocatable_function_3.f90
===================================================================
*** /svn/trunk/gcc/testsuite/gfortran.dg/allocatable_function_3.f90	(revision 0)
--- /svn/trunk/gcc/testsuite/gfortran.dg/allocatable_function_3.f90	(revision 0)
***************
*** 0 ****
--- 1,24 ----
+ ! { dg-do run }
+ ! Tests the fix for PR33986, in which the call to scram would call
+ ! an ICE because allocatable result actuals had not been catered for.
+ !
+ !  Contributed by Damian Rouson <damian@rouson.net>
+ !
+ function transform_to_spectral_from() result(spectral)
+   integer, allocatable :: spectral(:)
+   allocate(spectral(2))
+   call scram(spectral)
+ end function transform_to_spectral_from
+ 
+ subroutine scram (x)
+   integer x(2)
+   x = (/1,2/)
+ end subroutine
+ 
+   interface
+     function transform_to_spectral_from() result(spectral)
+       integer, allocatable :: spectral(:)
+     end function transform_to_spectral_from
+   end interface
+   if (any (transform_to_spectral_from () .ne. (/1,2/))) call abort ()
+ end
Index: /svn/trunk/gcc/fortran/trans-array.c
===================================================================
*** /svn/trunk/gcc/fortran/trans-array.c	(revision 130157)
--- /svn/trunk/gcc/fortran/trans-array.c	(working copy)
*************** gfc_conv_array_parameter (gfc_se * se, g
*** 5003,5009 ****
          }
        if (sym->attr.allocatable)
          {
! 	  if (sym->attr.dummy)
  	    {
  	      gfc_conv_expr_descriptor (se, expr, ss);
  	      se->expr = gfc_conv_array_data (se->expr);
--- 5003,5009 ----
          }
        if (sym->attr.allocatable)
          {
! 	  if (sym->attr.dummy || sym->attr.result)
  	    {
  	      gfc_conv_expr_descriptor (se, expr, ss);
  	      se->expr = gfc_conv_array_data (se->expr);

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

* Re: [Patch, fortran] PR33986 - ICE on allocatable function result
  2007-11-14 11:17 ` Paul Richard Thomas
@ 2007-11-14 15:15   ` Tobias Burnus
  2007-11-14 17:02   ` Jerry DeLisle
  1 sibling, 0 replies; 4+ messages in thread
From: Tobias Burnus @ 2007-11-14 15:15 UTC (permalink / raw)
  To: Paul Richard Thomas; +Cc: gcc-patches, fortran

>
> This is another self-explanatory patch, where allocatable function
> results were just plain forgotten.
> Boostrapped and regtested on x86_ia64 - OK for trunk?
OK. Thanks for the fix.


Paul Richard Thomas wrote:
> Sorry, I addeddd the previous patch - herewith the correct one.
>   

Tobias

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

* Re: [Patch, fortran] PR33986 - ICE on allocatable function result
  2007-11-14 11:17 ` Paul Richard Thomas
  2007-11-14 15:15   ` Tobias Burnus
@ 2007-11-14 17:02   ` Jerry DeLisle
  1 sibling, 0 replies; 4+ messages in thread
From: Jerry DeLisle @ 2007-11-14 17:02 UTC (permalink / raw)
  To: Paul Richard Thomas; +Cc: gcc-patches, fortran

Paul Richard Thomas wrote:
> Sorry, I addeddd the previous patch - herewith the correct one.
> 
> Paul
OK

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

end of thread, other threads:[~2007-11-14 15:29 UTC | newest]

Thread overview: 4+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2007-11-14 10:55 [Patch, fortran] PR33986 - ICE on allocatable function result Paul Richard Thomas
2007-11-14 11:17 ` Paul Richard Thomas
2007-11-14 15:15   ` Tobias Burnus
2007-11-14 17:02   ` Jerry DeLisle

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