public inbox for gcc-patches@gcc.gnu.org
 help / color / mirror / Atom feed
* Re: [PATCH, FORTRAN] Fix PR fortran/60718
@ 2014-04-11 11:37 Tobias Burnus
  2014-04-11 12:40 ` Bernd Edlinger
  0 siblings, 1 reply; 7+ messages in thread
From: Tobias Burnus @ 2014-04-11 11:37 UTC (permalink / raw)
  To: Bernd Edlinger; +Cc: gcc-patches, fortran

Hi Bernd,

Bernd Edlinger wrote:
> It was caused by a strict aliasing violation, when passing a value of the type
> "class(x),pointer" to a formal procedure parameter of the type "class(x),target".

I assume a VIEW_CONVERT_EXPR is directly on the argument is insufficient? Otherwise,
I think I would prefer that:

+		      gfc_conv_expr (&parmse, e);
+		      parmse.expr = fold_build1_loc (input_location,
+						       VIEW_CONVERT_EXPR,
+						       type, parmse.expr));
+		      parmse.expr = gfc_build_addr_expr (parmse.expr)


Otherwise, the approach of using a temporary is okay, but I believe the condition

> +		  else if (e->ts.type == BT_CLASS && fsym
> +			   && fsym->ts.type == BT_CLASS
> +			   && fsym->attr.target)

is wrong. What you intent to do is independent of the target attribute (~ restrict
qualifier).


We have three different cases:

* Allocatable
* Pointer
* Nonalloc/nonpointer

Besides staying in one's own group, one can do:

Pointer -> Nonalloc
Allocatable - > Noalloc
Nonallocatable*/Allocatable* -> Pointer with intent(in)

* = must have the target attribute

Thus, you need to handle those; gfc_expr_attr(e) should give you
information about the expression. Or one could always check against
   gfc_typenode_for_spec (&fsym->ts);
of both fsym and e.

Tobias

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

* RE: [PATCH, FORTRAN] Fix PR fortran/60718
  2014-04-11 11:37 [PATCH, FORTRAN] Fix PR fortran/60718 Tobias Burnus
@ 2014-04-11 12:40 ` Bernd Edlinger
  2014-04-11 14:05   ` Tobias Burnus
  0 siblings, 1 reply; 7+ messages in thread
From: Bernd Edlinger @ 2014-04-11 12:40 UTC (permalink / raw)
  To: Tobias Burnus; +Cc: gcc-patches, fortran

Hi Tobias,

On Fri, 11 Apr 2014 13:37:46, Tobias Burnus wrote:
>
> Hi Bernd,
>
> Bernd Edlinger wrote:
>> It was caused by a strict aliasing violation, when passing a value of the type
>> "class(x),pointer" to a formal procedure parameter of the type "class(x),target".
>
> I assume a VIEW_CONVERT_EXPR is directly on the argument is insufficient? Otherwise,
> I think I would prefer that:
>
> + gfc_conv_expr (&parmse, e);
> + parmse.expr = fold_build1_loc (input_location,
> + VIEW_CONVERT_EXPR,
> + type, parmse.expr));
> + parmse.expr = gfc_build_addr_expr (parmse.expr)
>
>
> Otherwise, the approach of using a temporary is okay, but I believe the condition
>

Yes, I tried that qickly, but this does not fix the test case.

>> + else if (e->ts.type == BT_CLASS && fsym
>> + && fsym->ts.type == BT_CLASS
>> + && fsym->attr.target)
>
> is wrong. What you intent to do is independent of the target attribute (~ restrict
> qualifier).
>

Hmm,

I was hoping somehow that only that test case is broken,
and needs to be fixed. The target attribute is somehow simple,
it implies intent(in) and the actual value will in most cases
be a pointer, as in the example.

>
> We have three different cases:
>
> * Allocatable
> * Pointer
> * Nonalloc/nonpointer
>
> Besides staying in one's own group, one can do:
>
> Pointer -> Nonalloc
> Allocatable -> Noalloc
> Nonallocatable*/Allocatable* -> Pointer with intent(in)
>
> * = must have the target attribute
>

Well, this approach does not handle intent(inout) at all.

If that is possible, the changed value must be written back again.

Are there any test cases for these conversions?


> Thus, you need to handle those; gfc_expr_attr(e) should give you
> information about the expression. Or one could always check against
> gfc_typenode_for_spec (&fsym->ts);
> of both fsym and e.
>

I am not sure, does gfc_typenode_for_spec always allocate new nodes?



Thanks
Bernd.

> Tobias


 		 	   		  

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

* Re: [PATCH, FORTRAN] Fix PR fortran/60718
  2014-04-11 12:40 ` Bernd Edlinger
@ 2014-04-11 14:05   ` Tobias Burnus
  2014-04-15 11:49     ` Bernd Edlinger
  0 siblings, 1 reply; 7+ messages in thread
From: Tobias Burnus @ 2014-04-11 14:05 UTC (permalink / raw)
  To: Bernd Edlinger; +Cc: gcc-patches, fortran

Hi Tobias,

On Fri, Apr 11, 2014 at 02:39:57PM +0200, Bernd Edlinger wrote:
> On Fri, 11 Apr 2014 13:37:46, Tobias Burnus wrote:
> Hmm,
> 
> I was hoping somehow that only that test case is broken,
> and needs to be fixed. The target attribute is somehow simple,
> it implies intent(in) and the actual value will in most cases
> be a pointer, as in the example.

I think that passing another nonpointer TARGET to a dummy argument
which has a TARGET attribute is at least as common as passing a
POINTER to a TARGET.

TARGET is roughtly the opposite to the restrict qualifier. By default
any nonpointer variable does not alias with something else, unless
it has the TARGET attribute; if it has, it (its address) can then
be assigned to a pointer. POINTER intrinsically alias and cannot
have the TARGET attribute.

> > Pointer -> Nonalloc
> > Allocatable -> Noalloc
> > Nonallocatable*/Allocatable* -> Pointer with intent(in)
> 
> Well, this approach does not handle intent(inout) at all.


Note: Intent(in) can mean two different things. For normal variables,
it means that those may not be modified at all (although, the value
 but not address of pointer components of structs [derived types]
is permitted to be changed). And for pointers, it means that the
pointer association status may not be changed (i.e. the pointer
address, allocating, deallocating) - the value of the variable to
which the pointer points to may still be modified.


> If that is possible, the changed value must be written back again.
> Are there any test cases for these conversions?

For normal variables: Sure. For polymorphic variables, I have no idea.

I am also not sure whether the value has to be written back or not; if
only the value of the address pointed to changes and not the pointer
itself (which can't in this context), everything should be fine.


In any case, I am not really happy with the way we handle polymorphic
types - and I am considering to change it when we implement the new
array descriptor.

Another issue is the handling of the restrict qualifier. GCC's
implementation is not really compatible with the Fortran standard and
gfortran's use. To fix that properly, we need Michael Matz restrict
patch ...

> > Thus, you need to handle those; gfc_expr_attr(e) should give you
> > information about the expression. Or one could always check against
> > gfc_typenode_for_spec (&fsym->ts);
> > of both fsym and e.
> >
> 
> I am not sure, does gfc_typenode_for_spec always allocate new nodes?

No idea - I had to look at the source code.

Tobias

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

* RE: [PATCH, FORTRAN] Fix PR fortran/60718
  2014-04-11 14:05   ` Tobias Burnus
@ 2014-04-15 11:49     ` Bernd Edlinger
  2014-04-30 14:13       ` [PING] " Bernd Edlinger
  2014-12-02 10:25       ` [PATCH, REPOST] " Bernd Edlinger
  0 siblings, 2 replies; 7+ messages in thread
From: Bernd Edlinger @ 2014-04-15 11:49 UTC (permalink / raw)
  To: Tobias Burnus; +Cc: gcc-patches, fortran

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

Hi Tobias,

On Fri, 11 Apr 2014 16:04:51, Tobias Burnus wrote:
>
> Hi Tobias,
>
> On Fri, Apr 11, 2014 at 02:39:57PM +0200, Bernd Edlinger wrote:
>> On Fri, 11 Apr 2014 13:37:46, Tobias Burnus wrote:
>> Hmm,
>>
>> I was hoping somehow that only that test case is broken,
>> and needs to be fixed. The target attribute is somehow simple,
>> it implies intent(in) and the actual value will in most cases
>> be a pointer, as in the example.
>
> I think that passing another nonpointer TARGET to a dummy argument
> which has a TARGET attribute is at least as common as passing a
> POINTER to a TARGET.
>
> TARGET is roughtly the opposite to the restrict qualifier. By default
> any nonpointer variable does not alias with something else, unless
> it has the TARGET attribute; if it has, it (its address) can then
> be assigned to a pointer. POINTER intrinsically alias and cannot
> have the TARGET attribute.
>
>>> Pointer -> Nonalloc
>>> Allocatable -> Noalloc
>>> Nonallocatable*/Allocatable* -> Pointer with intent(in)
>>
>> Well, this approach does not handle intent(inout) at all.
>
>

Now I have created a test case for the different aliasing issues
with may arise with scalar objects.

As you pointed out, also conversions of allocatable -> nonalloc,
allocatable -> pointer and nonalloc -> pointer  turn out to
violate the strict aliasing rules. However, conversions of
arrays of objects with different attributes seem to be safe.

I have not been able to find an example where it would be
necessary to write the modified class object back to the original
location. But I am not really a Fortran expert.

Unfortunately there are also conversions of optional allocatable ->
optional pointer, which complicate the whole thing quite a lot.
I have found these in class_optional_2.f90.

Boot-strapped and regression-tested on x86_64-linux-gnu.
OK for trunk?


Thanks
Bernd.
 		 	   		  

[-- Attachment #2: changelog-pr60718.txt --]
[-- Type: text/plain, Size: 258 bytes --]

2014-04-15  Bernd Edlinger  <bernd.edlinger@hotmail.de>

	PR fortran/60718
	* trans-expr.c (gfc_conv_procedure_call): Fix a strict aliasing
	violation when passing a class object to a formal parameter which has
	different pointer or allocatable attributes.


[-- Attachment #3: patch-pr60718.diff --]
[-- Type: application/octet-stream, Size: 5245 bytes --]

Index: gcc/fortran/trans-expr.c
===================================================================
--- gcc/fortran/trans-expr.c	(revision 209307)
+++ gcc/fortran/trans-expr.c	(working copy)
@@ -4244,6 +4244,55 @@ gfc_conv_procedure_call (gfc_se * se, gfc_symbol *
 				     fsym->attr.optional
 				     && e->expr_type == EXPR_VARIABLE);
 		    }
+		  else if (e->ts.type == BT_CLASS && fsym
+			   && fsym->ts.type == BT_CLASS
+			   && !CLASS_DATA (fsym)->as
+			   && !CLASS_DATA (e)->as
+			   && (CLASS_DATA (fsym)->attr.class_pointer
+			       != CLASS_DATA (e)->attr.class_pointer
+			       || CLASS_DATA (fsym)->attr.allocatable
+				  != CLASS_DATA (e)->attr.allocatable))
+		    {
+		      type = gfc_typenode_for_spec (&fsym->ts);
+		      var = gfc_create_var (type, fsym->name);
+		      gfc_conv_expr (&parmse, e);
+		      if (fsym->attr.optional
+			  && e->expr_type == EXPR_VARIABLE
+			  && e->symtree->n.sym->attr.optional)
+			{
+			  stmtblock_t block;
+			  tree cond;
+			  tmp = gfc_build_addr_expr (NULL_TREE, parmse.expr);
+			  cond = fold_build2_loc (input_location, NE_EXPR,
+						  boolean_type_node, tmp,
+						  fold_convert (TREE_TYPE (tmp),
+							    null_pointer_node));
+			  gfc_start_block (&block);
+			  gfc_add_modify (&block, var,
+					  fold_build1_loc (input_location,
+							   VIEW_CONVERT_EXPR,
+							   type, parmse.expr));
+			  gfc_add_expr_to_block (&parmse.pre,
+				 fold_build3_loc (input_location,
+					 COND_EXPR, void_type_node,
+					 cond, gfc_finish_block (&block),
+					 build_empty_stmt (input_location)));
+			  parmse.expr = gfc_build_addr_expr (NULL_TREE, var);
+			  parmse.expr = build3_loc (input_location, COND_EXPR,
+					 TREE_TYPE (parmse.expr),
+					 cond, parmse.expr,
+					 fold_convert (TREE_TYPE (parmse.expr),
+						       null_pointer_node));
+			}
+		      else
+			{
+			  gfc_add_modify (&parmse.pre, var,
+					  fold_build1_loc (input_location,
+							   VIEW_CONVERT_EXPR,
+							   type, parmse.expr));
+			  parmse.expr = gfc_build_addr_expr (NULL_TREE, var);
+			}
+		    }
 		  else
 		    gfc_conv_expr_reference (&parmse, e);
 
Index: gcc/testsuite/gfortran.dg/class_alias.f90
===================================================================
--- gcc/testsuite/gfortran.dg/class_alias.f90	(revision 0)
+++ gcc/testsuite/gfortran.dg/class_alias.f90	(revision 0)
@@ -0,0 +1,95 @@
+! { dg-do run }
+! { dg-options "-fdump-tree-original" }
+!
+! test for aliasing violations when converting class objects with
+! different target and pointer attributes.
+!
+module test_module
+
+  implicit none
+
+  type, public :: test
+    integer :: x
+  end type test
+
+contains
+
+  subroutine do_it6 (par2_t)
+    class (test), target :: par2_t
+    par2_t%x = par2_t%x + 1
+  end subroutine do_it6
+   
+  subroutine do_it5 (par1_p)
+    class (test), pointer, intent(in) :: par1_p
+    ! pointer -> target
+    ! { dg-final { scan-tree-dump "par2_t\[^\n]*VIEW_CONVERT_EXPR\[^\n]*par1_p" "original" } }
+    call do_it6 (par1_p)
+  end subroutine do_it5
+
+  subroutine do_it4 (par_p)
+    class (test), pointer, intent(in) :: par_p
+    ! pointer -> pointer
+    ! { dg-final { scan-tree-dump-not "par1_p\[^\n]*VIEW_CONVERT_EXPR\[^\n]*par_p" "original" } }
+    call do_it5 (par_p)
+  end subroutine do_it4
+
+  subroutine do_it3 (par1_t)
+    class (test), target :: par1_t
+    ! target -> pointer
+    ! { dg-final { scan-tree-dump "par_p\[^\n]*VIEW_CONVERT_EXPR\[^\n]*par1_t" "original" } }
+    call do_it4 (par1_t)
+  end subroutine do_it3
+
+  subroutine do_it2 (par_t)
+    class (test), target :: par_t
+    ! target -> target
+    ! { dg-final { scan-tree-dump-not "par1_t\[^\n]*VIEW_CONVERT_EXPR\[^\n]*par_t" "original" } }
+    call do_it3 (par_t)
+  end subroutine do_it2
+
+  subroutine do_it1 (par1_a)
+    class (test), allocatable :: par1_a
+    ! allocatable -> target
+    ! { dg-final { scan-tree-dump "par_t\[^\n]*VIEW_CONVERT_EXPR\[^\n]*par1_a" "original" } }
+    call do_it2 (par1_a)
+  end subroutine do_it1
+
+  subroutine do_it (par_a)
+    class (test), allocatable :: par_a
+    ! allocatable -> allocatable
+    ! { dg-final { scan-tree-dump-not "par1_a\[^\n]*VIEW_CONVERT_EXPR\[^\n]*par_a" "original" } }
+    call do_it1 (par_a)
+  end subroutine do_it
+
+end module test_module
+
+use test_module
+
+  implicit none
+  class (test), allocatable :: var_a
+  class (test), pointer :: var_p
+
+
+  allocate (var_a)
+  allocate (var_p)
+  var_a%x = 0
+  var_p%x = 0
+  
+  ! allocatable -> allocatable
+  ! { dg-final { scan-tree-dump-not "par_a\[^\n]*VIEW_CONVERT_EXPR\[^\n]*var_a" "original" } }
+  call do_it (var_a)
+  ! allocatable -> target
+  ! { dg-final { scan-tree-dump "par_t\[^\n]*VIEW_CONVERT_EXPR\[^\n]*var_a" "original" } }
+  call do_it2 (var_a)
+  ! pointer -> target
+  ! { dg-final { scan-tree-dump "par_t\[^\n]*VIEW_CONVERT_EXPR\[^\n]*var_p" "original" } }
+  call do_it2 (var_p)
+  ! pointer -> pointer
+  ! { dg-final { scan-tree-dump-not "par_p\[^\n]*VIEW_CONVERT_EXPR\[^\n]*var_p" "original" } }
+  call do_it4 (var_p)
+  if (var_a%x .ne. 2) call abort()
+  if (var_p%x .ne. 2) call abort()
+  deallocate (var_a)
+  deallocate (var_p)
+end
+! { dg-final { cleanup-tree-dump "original" } }

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

* [PING] [PATCH, FORTRAN] Fix PR fortran/60718
  2014-04-15 11:49     ` Bernd Edlinger
@ 2014-04-30 14:13       ` Bernd Edlinger
  2014-06-02 13:32         ` [PING**2] " Bernd Edlinger
  2014-12-02 10:25       ` [PATCH, REPOST] " Bernd Edlinger
  1 sibling, 1 reply; 7+ messages in thread
From: Bernd Edlinger @ 2014-04-30 14:13 UTC (permalink / raw)
  To: Tobias Burnus; +Cc: gcc-patches, fortran

Ping...

> Date: Tue, 15 Apr 2014 13:49:37 +0200
>
> Hi Tobias,
>
> On Fri, 11 Apr 2014 16:04:51, Tobias Burnus wrote:
>>
>> Hi Tobias,
>>
>> On Fri, Apr 11, 2014 at 02:39:57PM +0200, Bernd Edlinger wrote:
>>> On Fri, 11 Apr 2014 13:37:46, Tobias Burnus wrote:
>>> Hmm,
>>>
>>> I was hoping somehow that only that test case is broken,
>>> and needs to be fixed. The target attribute is somehow simple,
>>> it implies intent(in) and the actual value will in most cases
>>> be a pointer, as in the example.
>>
>> I think that passing another nonpointer TARGET to a dummy argument
>> which has a TARGET attribute is at least as common as passing a
>> POINTER to a TARGET.
>>
>> TARGET is roughtly the opposite to the restrict qualifier. By default
>> any nonpointer variable does not alias with something else, unless
>> it has the TARGET attribute; if it has, it (its address) can then
>> be assigned to a pointer. POINTER intrinsically alias and cannot
>> have the TARGET attribute.
>>
>>>> Pointer -> Nonalloc
>>>> Allocatable -> Noalloc
>>>> Nonallocatable*/Allocatable* -> Pointer with intent(in)
>>>
>>> Well, this approach does not handle intent(inout) at all.
>>
>>
>
> Now I have created a test case for the different aliasing issues
> with may arise with scalar objects.
>
> As you pointed out, also conversions of allocatable -> nonalloc,
> allocatable -> pointer and nonalloc -> pointer  turn out to
> violate the strict aliasing rules. However, conversions of
> arrays of objects with different attributes seem to be safe.
>
> I have not been able to find an example where it would be
> necessary to write the modified class object back to the original
> location. But I am not really a Fortran expert.
>
> Unfortunately there are also conversions of optional allocatable ->
> optional pointer, which complicate the whole thing quite a lot.
> I have found these in class_optional_2.f90.
>
> Boot-strapped and regression-tested on x86_64-linux-gnu.
> OK for trunk?
>
>
> Thanks
> Bernd.
>
 		 	   		  

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

* [PING**2] [PATCH, FORTRAN] Fix PR fortran/60718
  2014-04-30 14:13       ` [PING] " Bernd Edlinger
@ 2014-06-02 13:32         ` Bernd Edlinger
  0 siblings, 0 replies; 7+ messages in thread
From: Bernd Edlinger @ 2014-06-02 13:32 UTC (permalink / raw)
  To: Tobias Burnus; +Cc: gcc-patches, fortran

Hello,

Ping**2...

this is patch still pending:

see https://gcc.gnu.org/ml/gcc-patches/2014-04/msg00774.html
for the latest version.

Thanks,
Bernd.


> Date: Wed, 30 Apr 2014 15:17:51 +0200
>
> Ping...
>
>> Date: Tue, 15 Apr 2014 13:49:37 +0200
>>
>> Hi Tobias,
>>
>> On Fri, 11 Apr 2014 16:04:51, Tobias Burnus wrote:
>>>
>>> Hi Tobias,
>>>
>>> On Fri, Apr 11, 2014 at 02:39:57PM +0200, Bernd Edlinger wrote:
>>>> On Fri, 11 Apr 2014 13:37:46, Tobias Burnus wrote:
>>>> Hmm,
>>>>
>>>> I was hoping somehow that only that test case is broken,
>>>> and needs to be fixed. The target attribute is somehow simple,
>>>> it implies intent(in) and the actual value will in most cases
>>>> be a pointer, as in the example.
>>>
>>> I think that passing another nonpointer TARGET to a dummy argument
>>> which has a TARGET attribute is at least as common as passing a
>>> POINTER to a TARGET.
>>>
>>> TARGET is roughtly the opposite to the restrict qualifier. By default
>>> any nonpointer variable does not alias with something else, unless
>>> it has the TARGET attribute; if it has, it (its address) can then
>>> be assigned to a pointer. POINTER intrinsically alias and cannot
>>> have the TARGET attribute.
>>>
>>>>> Pointer -> Nonalloc
>>>>> Allocatable -> Noalloc
>>>>> Nonallocatable*/Allocatable* -> Pointer with intent(in)
>>>>
>>>> Well, this approach does not handle intent(inout) at all.
>>>
>>>
>>
>> Now I have created a test case for the different aliasing issues
>> with may arise with scalar objects.
>>
>> As you pointed out, also conversions of allocatable -> nonalloc,
>> allocatable -> pointer and nonalloc -> pointer turn out to
>> violate the strict aliasing rules. However, conversions of
>> arrays of objects with different attributes seem to be safe.
>>
>> I have not been able to find an example where it would be
>> necessary to write the modified class object back to the original
>> location. But I am not really a Fortran expert.
>>
>> Unfortunately there are also conversions of optional allocatable ->
>> optional pointer, which complicate the whole thing quite a lot.
>> I have found these in class_optional_2.f90.
>>
>> Boot-strapped and regression-tested on x86_64-linux-gnu.
>> OK for trunk?
>>
>>
>> Thanks
>> Bernd.
>>
>
 		 	   		  

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

* [PATCH, REPOST] Fix PR fortran/60718
  2014-04-15 11:49     ` Bernd Edlinger
  2014-04-30 14:13       ` [PING] " Bernd Edlinger
@ 2014-12-02 10:25       ` Bernd Edlinger
  1 sibling, 0 replies; 7+ messages in thread
From: Bernd Edlinger @ 2014-12-02 10:25 UTC (permalink / raw)
  To: Tobias Burnus; +Cc: gcc-patches, fortran

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

Hello Tobias,

a long time ago, I posted this patch, but it got forgotten.
However the described problem is still unsolved,
so I thought my patch should be re-posted now.


Boot-strapped and regression-tested on arm-linux-gnueabihf.
OK for trunk?


Thanks
Bernd.



On Tue, 15 Apr 2014 13:49:37, Bernd Edlinger wrote:
>
> Hi Tobias,
>
> On Fri, 11 Apr 2014 16:04:51, Tobias Burnus wrote:
>>
>> Hi Tobias,
>>
>> On Fri, Apr 11, 2014 at 02:39:57PM +0200, Bernd Edlinger wrote:
>>> On Fri, 11 Apr 2014 13:37:46, Tobias Burnus wrote:
>>> Hmm,
>>>
>>> I was hoping somehow that only that test case is broken,
>>> and needs to be fixed. The target attribute is somehow simple,
>>> it implies intent(in) and the actual value will in most cases
>>> be a pointer, as in the example.
>>
>> I think that passing another nonpointer TARGET to a dummy argument
>> which has a TARGET attribute is at least as common as passing a
>> POINTER to a TARGET.
>>
>> TARGET is roughtly the opposite to the restrict qualifier. By default
>> any nonpointer variable does not alias with something else, unless
>> it has the TARGET attribute; if it has, it (its address) can then
>> be assigned to a pointer. POINTER intrinsically alias and cannot
>> have the TARGET attribute.
>>
>>>> Pointer -> Nonalloc
>>>> Allocatable -> Noalloc
>>>> Nonallocatable*/Allocatable* -> Pointer with intent(in)
>>>
>>> Well, this approach does not handle intent(inout) at all.
>>
>>
>
> Now I have created a test case for the different aliasing issues
> with may arise with scalar objects.
>
> As you pointed out, also conversions of allocatable -> nonalloc,
> allocatable -> pointer and nonalloc -> pointer  turn out to
> violate the strict aliasing rules. However, conversions of
> arrays of objects with different attributes seem to be safe.
>
> I have not been able to find an example where it would be
> necessary to write the modified class object back to the original
> location. But I am not really a Fortran expert.
>
> Unfortunately there are also conversions of optional allocatable ->
> optional pointer, which complicate the whole thing quite a lot.
> I have found these in class_optional_2.f90.
>
> Boot-strapped and regression-tested on x86_64-linux-gnu.
> OK for trunk?
>
>
> Thanks
> Bernd.
>
 		 	   		  

[-- Attachment #2: changelog-pr60718.txt --]
[-- Type: text/plain, Size: 382 bytes --]

2014-04-15  Bernd Edlinger  <bernd.edlinger@hotmail.de>

	PR fortran/60718
	* trans-expr.c (gfc_conv_procedure_call): Fix a strict aliasing
	violation when passing a class object to a formal parameter which has
	different pointer or allocatable attributes.

testsuite:
2014-04-14  Bernd Edlinger  <bernd.edlinger@hotmail.de>

	PR fortran/60718
	* gfortran.dg/class_alias.f90: New.


[-- Attachment #3: patch-pr60718.diff --]
[-- Type: application/octet-stream, Size: 5245 bytes --]

Index: gcc/fortran/trans-expr.c
===================================================================
--- gcc/fortran/trans-expr.c	(revision 209307)
+++ gcc/fortran/trans-expr.c	(working copy)
@@ -4244,6 +4244,55 @@ gfc_conv_procedure_call (gfc_se * se, gfc_symbol *
 				     fsym->attr.optional
 				     && e->expr_type == EXPR_VARIABLE);
 		    }
+		  else if (e->ts.type == BT_CLASS && fsym
+			   && fsym->ts.type == BT_CLASS
+			   && !CLASS_DATA (fsym)->as
+			   && !CLASS_DATA (e)->as
+			   && (CLASS_DATA (fsym)->attr.class_pointer
+			       != CLASS_DATA (e)->attr.class_pointer
+			       || CLASS_DATA (fsym)->attr.allocatable
+				  != CLASS_DATA (e)->attr.allocatable))
+		    {
+		      type = gfc_typenode_for_spec (&fsym->ts);
+		      var = gfc_create_var (type, fsym->name);
+		      gfc_conv_expr (&parmse, e);
+		      if (fsym->attr.optional
+			  && e->expr_type == EXPR_VARIABLE
+			  && e->symtree->n.sym->attr.optional)
+			{
+			  stmtblock_t block;
+			  tree cond;
+			  tmp = gfc_build_addr_expr (NULL_TREE, parmse.expr);
+			  cond = fold_build2_loc (input_location, NE_EXPR,
+						  boolean_type_node, tmp,
+						  fold_convert (TREE_TYPE (tmp),
+							    null_pointer_node));
+			  gfc_start_block (&block);
+			  gfc_add_modify (&block, var,
+					  fold_build1_loc (input_location,
+							   VIEW_CONVERT_EXPR,
+							   type, parmse.expr));
+			  gfc_add_expr_to_block (&parmse.pre,
+				 fold_build3_loc (input_location,
+					 COND_EXPR, void_type_node,
+					 cond, gfc_finish_block (&block),
+					 build_empty_stmt (input_location)));
+			  parmse.expr = gfc_build_addr_expr (NULL_TREE, var);
+			  parmse.expr = build3_loc (input_location, COND_EXPR,
+					 TREE_TYPE (parmse.expr),
+					 cond, parmse.expr,
+					 fold_convert (TREE_TYPE (parmse.expr),
+						       null_pointer_node));
+			}
+		      else
+			{
+			  gfc_add_modify (&parmse.pre, var,
+					  fold_build1_loc (input_location,
+							   VIEW_CONVERT_EXPR,
+							   type, parmse.expr));
+			  parmse.expr = gfc_build_addr_expr (NULL_TREE, var);
+			}
+		    }
 		  else
 		    gfc_conv_expr_reference (&parmse, e);
 
Index: gcc/testsuite/gfortran.dg/class_alias.f90
===================================================================
--- gcc/testsuite/gfortran.dg/class_alias.f90	(revision 0)
+++ gcc/testsuite/gfortran.dg/class_alias.f90	(revision 0)
@@ -0,0 +1,95 @@
+! { dg-do run }
+! { dg-options "-fdump-tree-original" }
+!
+! test for aliasing violations when converting class objects with
+! different target and pointer attributes.
+!
+module test_module
+
+  implicit none
+
+  type, public :: test
+    integer :: x
+  end type test
+
+contains
+
+  subroutine do_it6 (par2_t)
+    class (test), target :: par2_t
+    par2_t%x = par2_t%x + 1
+  end subroutine do_it6
+   
+  subroutine do_it5 (par1_p)
+    class (test), pointer, intent(in) :: par1_p
+    ! pointer -> target
+    ! { dg-final { scan-tree-dump "par2_t\[^\n]*VIEW_CONVERT_EXPR\[^\n]*par1_p" "original" } }
+    call do_it6 (par1_p)
+  end subroutine do_it5
+
+  subroutine do_it4 (par_p)
+    class (test), pointer, intent(in) :: par_p
+    ! pointer -> pointer
+    ! { dg-final { scan-tree-dump-not "par1_p\[^\n]*VIEW_CONVERT_EXPR\[^\n]*par_p" "original" } }
+    call do_it5 (par_p)
+  end subroutine do_it4
+
+  subroutine do_it3 (par1_t)
+    class (test), target :: par1_t
+    ! target -> pointer
+    ! { dg-final { scan-tree-dump "par_p\[^\n]*VIEW_CONVERT_EXPR\[^\n]*par1_t" "original" } }
+    call do_it4 (par1_t)
+  end subroutine do_it3
+
+  subroutine do_it2 (par_t)
+    class (test), target :: par_t
+    ! target -> target
+    ! { dg-final { scan-tree-dump-not "par1_t\[^\n]*VIEW_CONVERT_EXPR\[^\n]*par_t" "original" } }
+    call do_it3 (par_t)
+  end subroutine do_it2
+
+  subroutine do_it1 (par1_a)
+    class (test), allocatable :: par1_a
+    ! allocatable -> target
+    ! { dg-final { scan-tree-dump "par_t\[^\n]*VIEW_CONVERT_EXPR\[^\n]*par1_a" "original" } }
+    call do_it2 (par1_a)
+  end subroutine do_it1
+
+  subroutine do_it (par_a)
+    class (test), allocatable :: par_a
+    ! allocatable -> allocatable
+    ! { dg-final { scan-tree-dump-not "par1_a\[^\n]*VIEW_CONVERT_EXPR\[^\n]*par_a" "original" } }
+    call do_it1 (par_a)
+  end subroutine do_it
+
+end module test_module
+
+use test_module
+
+  implicit none
+  class (test), allocatable :: var_a
+  class (test), pointer :: var_p
+
+
+  allocate (var_a)
+  allocate (var_p)
+  var_a%x = 0
+  var_p%x = 0
+  
+  ! allocatable -> allocatable
+  ! { dg-final { scan-tree-dump-not "par_a\[^\n]*VIEW_CONVERT_EXPR\[^\n]*var_a" "original" } }
+  call do_it (var_a)
+  ! allocatable -> target
+  ! { dg-final { scan-tree-dump "par_t\[^\n]*VIEW_CONVERT_EXPR\[^\n]*var_a" "original" } }
+  call do_it2 (var_a)
+  ! pointer -> target
+  ! { dg-final { scan-tree-dump "par_t\[^\n]*VIEW_CONVERT_EXPR\[^\n]*var_p" "original" } }
+  call do_it2 (var_p)
+  ! pointer -> pointer
+  ! { dg-final { scan-tree-dump-not "par_p\[^\n]*VIEW_CONVERT_EXPR\[^\n]*var_p" "original" } }
+  call do_it4 (var_p)
+  if (var_a%x .ne. 2) call abort()
+  if (var_p%x .ne. 2) call abort()
+  deallocate (var_a)
+  deallocate (var_p)
+end
+! { dg-final { cleanup-tree-dump "original" } }

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

end of thread, other threads:[~2014-12-02 10:25 UTC | newest]

Thread overview: 7+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2014-04-11 11:37 [PATCH, FORTRAN] Fix PR fortran/60718 Tobias Burnus
2014-04-11 12:40 ` Bernd Edlinger
2014-04-11 14:05   ` Tobias Burnus
2014-04-15 11:49     ` Bernd Edlinger
2014-04-30 14:13       ` [PING] " Bernd Edlinger
2014-06-02 13:32         ` [PING**2] " Bernd Edlinger
2014-12-02 10:25       ` [PATCH, REPOST] " Bernd Edlinger

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