public inbox for fortran@gcc.gnu.org
 help / color / mirror / Atom feed
* [Patch, fortran] PR67740 - Wrong association status of allocatable character pointer in derived types
@ 2023-10-11  8:48 Paul Richard Thomas
  2023-10-11 19:06 ` Harald Anlauf
  0 siblings, 1 reply; 4+ messages in thread
From: Paul Richard Thomas @ 2023-10-11  8:48 UTC (permalink / raw)
  To: fortran, gcc-patches


[-- Attachment #1.1: Type: text/plain, Size: 776 bytes --]

Hi All,

The title line of the PR should have been changed a long time since. As
noted in comment 5, the original problem was fixed in 10.5.

This patch fixes the problem described in comments 4 and 6, where the
hidden string length component was not being set in pointer assignment of
character arrays.

The fix regtests. OK for trunk and 13-branch?

Thanks are due to Harald for bringing this to my attention.

Paul

Fortran: Set hidden string length for pointer components [PR67440]

2023-10-11  Paul Thomas  <pault@gcc.gnu.org>

gcc/fortran
PR fortran/pr67740
* trans-expr.cc (gfc_trans_pointer_assignment): Set the hidden
string length component for pointer assignment to character
pointer components.

gcc/testsuite/
PR fortran/87477
* gfortran.dg/pr67740.f90: New test

[-- Attachment #2: pr67740.f90 --]
[-- Type: text/x-fortran, Size: 924 bytes --]

! {dg-do compile }
! { dg-options "-fdump-tree-original" }
!
! Check the fix for the testcase in comment 4, where the hidden string length
! component of the array pointer component was not set.
!
! Contributed by Sebastien Bardeau  <bardeau@iram.fr>
!
program test2
  implicit none
  character(len=10), allocatable, target :: s(:)
  character(len=:),  pointer             :: sptr(:)
  type :: pointer_typec0_t
    character(len=:), pointer :: data0
    character(len=:), pointer :: data1(:)
  end type pointer_typec0_t
  type(pointer_typec0_t) :: co
  !
  allocate(s(3))
  s(1) = '1234567890'
  s(2) = 'qwertyuio '
  s(3) = 'asdfghjk  '
  !
  sptr => s
  co%data0 => s(1)
  co%data1 => s
  !
  if (any (sptr .ne. s)) stop 1
  if (co%data0 .ne. s(1)) stop 2
  if (any (co%data1 .ne. s)) stop 3 ! Hidden string length was not set
end program test2
! { dg-final { scan-tree-dump-times "co._data1_length = 10;" 1 "original" } }

[-- Attachment #3: submit.diff --]
[-- Type: text/x-patch, Size: 1546 bytes --]

diff --git a/gcc/fortran/trans-expr.cc b/gcc/fortran/trans-expr.cc
index 860b73c4968..7beefa2e69c 100644
--- a/gcc/fortran/trans-expr.cc
+++ b/gcc/fortran/trans-expr.cc
@@ -10403,11 +10403,36 @@ gfc_trans_pointer_assignment (gfc_expr * expr1, gfc_expr * expr2)
 	}
 
       if (expr1->ts.type == BT_CHARACTER
-	  && expr1->symtree->n.sym->ts.deferred
-	  && expr1->symtree->n.sym->ts.u.cl->backend_decl
-	  && VAR_P (expr1->symtree->n.sym->ts.u.cl->backend_decl))
+	  && expr1->ts.deferred)
 	{
-	  tmp = expr1->symtree->n.sym->ts.u.cl->backend_decl;
+	  gfc_symbol *psym = expr1->symtree->n.sym;
+	  tmp = NULL_TREE;
+	  if (psym->ts.type == BT_CHARACTER)
+	    {
+	      gcc_assert (psym->ts.u.cl->backend_decl
+			  && VAR_P (psym->ts.u.cl->backend_decl));
+	      tmp = psym->ts.u.cl->backend_decl;
+	    }
+	  else if (expr1->ts.u.cl->backend_decl
+		   && VAR_P (expr1->ts.u.cl->backend_decl))
+	    tmp = expr1->ts.u.cl->backend_decl;
+	  else if (TREE_CODE (lse.expr) == COMPONENT_REF)
+	    {
+	      gfc_ref *ref = expr1->ref;
+	      for (;ref; ref = ref->next)
+		{
+		  if (ref->type == REF_COMPONENT
+		      && ref->u.c.component->ts.type == BT_CHARACTER
+		      && gfc_deferred_strlen (ref->u.c.component, &tmp))
+		    tmp = fold_build3_loc (input_location, COMPONENT_REF,
+					   TREE_TYPE (tmp),
+					   TREE_OPERAND (lse.expr, 0),
+					   tmp, NULL_TREE);
+		}
+	    }
+
+	  gcc_assert (tmp);
+
 	  if (expr2->expr_type != EXPR_NULL)
 	    gfc_add_modify (&block, tmp,
 			    fold_convert (TREE_TYPE (tmp), strlen_rhs));

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

* Re: [Patch, fortran] PR67740 - Wrong association status of allocatable character pointer in derived types
  2023-10-11  8:48 [Patch, fortran] PR67740 - Wrong association status of allocatable character pointer in derived types Paul Richard Thomas
@ 2023-10-11 19:06 ` Harald Anlauf
  2023-10-11 19:21   ` Harald Anlauf
  0 siblings, 1 reply; 4+ messages in thread
From: Harald Anlauf @ 2023-10-11 19:06 UTC (permalink / raw)
  To: Paul Richard Thomas, fortran, gcc-patches

Hi Paul,

On 10/11/23 10:48, Paul Richard Thomas wrote:
> Hi All,
>
> The title line of the PR should have been changed a long time since. As
> noted in comment 5, the original problem was fixed in 10.5.
>
> This patch fixes the problem described in comments 4 and 6, where the
> hidden string length component was not being set in pointer assignment of
> character arrays.
>
> The fix regtests. OK for trunk and 13-branch?

this is OK for both.

I'd suggest to wait a couple of days or a week before backporting.

Thanks for the patch!

Harald

> Thanks are due to Harald for bringing this to my attention.
>
> Paul
>
> Fortran: Set hidden string length for pointer components [PR67440]
>
> 2023-10-11  Paul Thomas  <pault@gcc.gnu.org>
>
> gcc/fortran
> PR fortran/pr67740
> * trans-expr.cc (gfc_trans_pointer_assignment): Set the hidden
> string length component for pointer assignment to character
> pointer components.
>
> gcc/testsuite/
> PR fortran/87477
> * gfortran.dg/pr67740.f90: New test
>


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

* Re: [Patch, fortran] PR67740 - Wrong association status of allocatable character pointer in derived types
  2023-10-11 19:06 ` Harald Anlauf
@ 2023-10-11 19:21   ` Harald Anlauf
  2023-10-11 22:21     ` Paul Richard Thomas
  0 siblings, 1 reply; 4+ messages in thread
From: Harald Anlauf @ 2023-10-11 19:21 UTC (permalink / raw)
  To: Paul Richard Thomas, fortran, gcc-patches

Hi Paul,

the patch is fine, but I forgot the mention that the testcase needs fixing:

Instead of

! {dg-do compile }

you'll likely want

! { dg-do run }

(Note the space before the dg-command.)

Cheers,
Harald

On 10/11/23 21:06, Harald Anlauf wrote:
> Hi Paul,
>
> On 10/11/23 10:48, Paul Richard Thomas wrote:
>> Hi All,
>>
>> The title line of the PR should have been changed a long time since. As
>> noted in comment 5, the original problem was fixed in 10.5.
>>
>> This patch fixes the problem described in comments 4 and 6, where the
>> hidden string length component was not being set in pointer assignment of
>> character arrays.
>>
>> The fix regtests. OK for trunk and 13-branch?
>
> this is OK for both.
>
> I'd suggest to wait a couple of days or a week before backporting.
>
> Thanks for the patch!
>
> Harald
>
>> Thanks are due to Harald for bringing this to my attention.
>>
>> Paul
>>
>> Fortran: Set hidden string length for pointer components [PR67440]
>>
>> 2023-10-11  Paul Thomas  <pault@gcc.gnu.org>
>>
>> gcc/fortran
>> PR fortran/pr67740
>> * trans-expr.cc (gfc_trans_pointer_assignment): Set the hidden
>> string length component for pointer assignment to character
>> pointer components.
>>
>> gcc/testsuite/
>> PR fortran/87477
>> * gfortran.dg/pr67740.f90: New test
>>
>
>


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

* Re: [Patch, fortran] PR67740 - Wrong association status of allocatable character pointer in derived types
  2023-10-11 19:21   ` Harald Anlauf
@ 2023-10-11 22:21     ` Paul Richard Thomas
  0 siblings, 0 replies; 4+ messages in thread
From: Paul Richard Thomas @ 2023-10-11 22:21 UTC (permalink / raw)
  To: Harald Anlauf; +Cc: fortran, gcc-patches, Bernhard Reutner-Fischer

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

Hi Harald and Bernhard,

Indeed, you are right about the space. However, the compile is intentional.
This catches the fix:
! { dg-final { scan-tree-dump-times "co._data1_length = 10;" 1 "original" }
}

Also, it helps to get the PR number right!

I was rushing to get the patch out before leaving for work and so even more
error prone than usual....

Cheers

Paul





On Wed, 11 Oct 2023 at 20:21, Harald Anlauf <anlauf@gmx.de> wrote:

> Hi Paul,
>
> the patch is fine, but I forgot the mention that the testcase needs fixing:
>
> Instead of
>
> ! {dg-do compile }
>
> you'll likely want
>
> ! { dg-do run }
>
> (Note the space before the dg-command.)
>
> Cheers,
> Harald
>
> On 10/11/23 21:06, Harald Anlauf wrote:
> > Hi Paul,
> >
> > On 10/11/23 10:48, Paul Richard Thomas wrote:
> >> Hi All,
> >>
> >> The title line of the PR should have been changed a long time since. As
> >> noted in comment 5, the original problem was fixed in 10.5.
> >>
> >> This patch fixes the problem described in comments 4 and 6, where the
> >> hidden string length component was not being set in pointer assignment
> of
> >> character arrays.
> >>
> >> The fix regtests. OK for trunk and 13-branch?
> >
> > this is OK for both.
> >
> > I'd suggest to wait a couple of days or a week before backporting.
> >
> > Thanks for the patch!
> >
> > Harald
> >
> >> Thanks are due to Harald for bringing this to my attention.
> >>
> >> Paul
> >>
> >> Fortran: Set hidden string length for pointer components [PR67440]
> >>
> >> 2023-10-11  Paul Thomas  <pault@gcc.gnu.org>
> >>
> >> gcc/fortran
> >> PR fortran/pr67740
> >> * trans-expr.cc (gfc_trans_pointer_assignment): Set the hidden
> >> string length component for pointer assignment to character
> >> pointer components.
> >>
> >> gcc/testsuite/
> >> PR fortran/87477
> >> * gfortran.dg/pr67740.f90: New test
> >>
> >
> >
>
>

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

end of thread, other threads:[~2023-10-11 22:21 UTC | newest]

Thread overview: 4+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2023-10-11  8:48 [Patch, fortran] PR67740 - Wrong association status of allocatable character pointer in derived types Paul Richard Thomas
2023-10-11 19:06 ` Harald Anlauf
2023-10-11 19:21   ` Harald Anlauf
2023-10-11 22:21     ` 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).