[Bug fortran/103312] [11/12/13/14/15 Regression] ICE in gfc_find_component since r9-1098-g3cf89a7b992d483e

2024-05-18 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103312

--- Comment #9 from Paul Thomas  ---
(In reply to Paul Thomas from comment #7)
> Created attachment 58231 [details]
> Preliminary fix for this PR
> 
> I went back to the beginning on this problem, having realised that it is far
> too early to resolve the compcall of a class argument in
> gfc_reduce_init_expr. Hence the chunk in expr.cc. The second chunk is
> (possibly) a bit of a kludge and, I would have thought, should be checked,
> at very least by checking that the class extends an abstract type. I will
> come back to this - yard duty calls!
> 
> A reduced test case, without the module 'example' and no type extension also
> failed and is now fixed. Also failing in this reduced testcase was:
> function func (this) result (string)
>   class(bar) :: this
>   character (:), allocatable :: string
>   allocate (character(this%size()) :: string)
>   string = repeat ("x", len (string))
> end function
> 
> Again, this is fixed.
> 
> Finally, the patch even regression tests OK :-)
> 
> Enough for now.
> 
> Paul

I just noticed that the version on my tree has expr guarded in the additional
condition in gfc_reduce_init_expr. Otherwise gfortran.dg/pr103588.f90
segfaults.

Paul

[Bug fortran/103312] [11/12/13/14/15 Regression] ICE in gfc_find_component since r9-1098-g3cf89a7b992d483e

2024-05-18 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103312

Paul Thomas  changed:

   What|Removed |Added

 CC||anlauf at gmx dot de

--- Comment #8 from Paul Thomas  ---
Hi Harald,

I put you in copy as a heads-up. I think that the patch of comment 7 will be
done and dusted by tomorrow night.

Regards

Paul

[Bug fortran/103312] [11/12/13/14/15 Regression] ICE in gfc_find_component since r9-1098-g3cf89a7b992d483e

2024-05-18 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103312

--- Comment #7 from Paul Thomas  ---
Created attachment 58231
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=58231=edit
Preliminary fix for this PR

I went back to the beginning on this problem, having realised that it is far
too early to resolve the compcall of a class argument in gfc_reduce_init_expr.
Hence the chunk in expr.cc. The second chunk is (possibly) a bit of a kludge
and, I would have thought, should be checked, at very least by checking that
the class extends an abstract type. I will come back to this - yard duty calls!

A reduced test case, without the module 'example' and no type extension also
failed and is now fixed. Also failing in this reduced testcase was:
function func (this) result (string)
  class(bar) :: this
  character (:), allocatable :: string
  allocate (character(this%size()) :: string)
  string = repeat ("x", len (string))
end function

Again, this is fixed.

Finally, the patch even regression tests OK :-)

Enough for now.

Paul

[Bug fortran/115070] [13/14/15 Regression] ICE using IEEE_ARITHMETIC in a derived type method with class, intent(out)

2024-05-17 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=115070

--- Comment #7 from Paul Thomas  ---
(In reply to Francois-Xavier Coudert from comment #6)
> So the var_decl in question is fpstate.0:
> 
>   type  type  size 
> unit-size 
> align:8 warn_if_not_align:0 symtab:0 alias-set -1 canonical-type
> 0x1035003f0 precision:8 min  max  0x1034bceb8 255>
> pointer_to_this >
> BLK
> size 
> unit-size 
> align:8 warn_if_not_align:0 symtab:0 alias-set -1 canonical-type
> 0x1036c4b28
> domain 
> DI
> size 
> unit-size 
> align:64 warn_if_not_align:0 symtab:0 alias-set -1
> canonical-type 0x1036c4a80 precision:64 min  max
> >
> pointer_to_this >
> addressable used ignored BLK s.f90:10:17 size  264> unit-size 
> align:8 warn_if_not_align:0 context >
> 
> And if I look at the tree dump, it seems the variable is indeed not created
> correctly:
> 
> __attribute__((fn spec (". w ")))
> void my_sub (struct __class_my_mod_My_type_t & restrict obs)
> {
>   try
> {
>   _gfortran_ieee_procedure_entry ((void *) );
> 
> see the missing declaration for fpstate.0. But it is created by
> gfc_create_var(), like so many other local variables in the front-end, so I
> have no idea why it's disappearing.

Thanks for both the comments, Francois-Xavier. I will look to see if, somehow,
the way in which the finalization is stacked on the function tree is somehow
overwriting the ieee entry call and or the decl of fpstate.0.

Paul

[Bug fortran/114874] [14/15 Regression] ICE with select type, type is (character(*)), and substring

2024-05-17 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=114874

Paul Thomas  changed:

   What|Removed |Added

 Resolution|--- |FIXED
 Status|NEW |RESOLVED

--- Comment #11 from Paul Thomas  ---
Hi Harald,

Your comments have been implemented and the patch committed to both affected
branches.

Thanks for the report and your help in honing up the fix.

Paul

[Bug fortran/115070] [13/14/15 Regression] ICE using IEEE_ARITHMETIC in a derived type method with class, intent(out)

2024-05-15 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=115070

Paul Thomas  changed:

   What|Removed |Added

 CC||fxcoudert at gmail dot com,
   ||pault at gcc dot gnu.org

--- Comment #3 from Paul Thomas  ---
(In reply to anlauf from comment #2)
> Replacing the scalar argument 'obs' by something with rank > 0 avoids the
> ICE,
> but then assumed-rank is not accepted with intent(out).  Another bug...

The tree output with 12-branch is:
__attribute__((fn spec (". r w ")))
void __copy_my_mod_My_type (struct my_type & restrict src, struct my_type &
restrict dst)
{
  *dst = *src;
}


__attribute__((fn spec (". w ")))
void my_sub (struct __class_my_mod_My_type_t & restrict obs)
{
  c_char fpstate.0[33];

  try
{
  _gfortran_ieee_procedure_entry ((void *) );
  if (obs->_vptr->_final != 0B)
{
  {
struct array00_my_type desc.1;

desc.1.dtype = {.elem_len=4, .rank=0, .type=5};
desc.1.data = (void * restrict) obs->_data;
desc.1.span = (integer(kind=8)) desc.1.dtype.elem_len;
obs->_vptr->_final (, obs->_vptr->_size, 0);
  }
}
  (void) __builtin_memcpy ((void *) obs->_data, (void *)
obs->_vptr->_def_init, (unsigned long) obs->_vptr->_size);

}
  finally
{
  _gfortran_ieee_procedure_exit ((void *) );
}
}

13- through 15-branches lack the default copy of the default initializer. This
disappeared with the fix for pr112407 and is required by the standard if the
derived type has no default initializer. This suggests a workaround, which
indeed "works":
  type my_type
integer :: a = 0
  end type my_type

I cannot see anything in the ieee procedures that would cause this but then I
know zip-all about ieee.

Putting Francois-Xavier in copy in the hope that he can shed some light.

Cheers

Paul

[Bug fortran/113363] ICE on ASSOCIATE and unlimited polymorphic function

2024-05-13 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=113363

--- Comment #10 from Paul Thomas  ---
Leave open partly because it is awaiting backporting to 14-branch but also
because there are remaining, pre-existing issues involving parentheses around
selector/source expressions:
https://gcc.gnu.org/pipermail/fortran/2024-May/060510.html

Paul

[Bug fortran/84006] [11/12/13/14 Regression] ICE in storage_size() with CLASS entity

2024-05-12 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84006

Paul Thomas  changed:

   What|Removed |Added

Summary|[11/12/13/14/15 Regression] |[11/12/13/14 Regression]
   |ICE in storage_size() with  |ICE in storage_size() with
   |CLASS entity|CLASS entity
 CC||pault at gcc dot gnu.org

--- Comment #15 from Paul Thomas  ---
Fixed on mainline. Will backport in a month.

Paul

[Bug fortran/98534] Intrinsic functions failing with unlimited polymorphic actual arguments

2024-05-12 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=98534

Paul Thomas  changed:

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution|--- |FIXED

--- Comment #7 from Paul Thomas  ---
Fixed on mainline.

Paul

[Bug fortran/100027] ICE on storage_size with polymorphic argument

2024-05-12 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=100027

Paul Thomas  changed:

   What|Removed |Added

 Resolution|--- |FIXED
 Status|NEW |RESOLVED

--- Comment #5 from Paul Thomas  ---
Fixed on mainline. Thanks for the report and the patch. It's a pity that you
didn't reply to me that you couldn't or wouldn't do the commit :-(

Paul

[Bug fortran/89462] [11/12/13 Regression] gfortran loops in code generation

2024-05-08 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89462

Paul Thomas  changed:

   What|Removed |Added

 Resolution|--- |FIXED
 Status|NEW |RESOLVED

--- Comment #18 from Paul Thomas  ---
Fixed on 13- through 15-branches.

Thanks for the report.

Paul

[Bug fortran/93678] [11/12/13 Regression] ICE with TRANSFER and typebound procedures

2024-05-08 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=93678

Paul Thomas  changed:

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution|--- |FIXED

--- Comment #18 from Paul Thomas  ---
Fixed on 13- through 15-branches. Thanks for the report.

Paul

[Bug fortran/113956] [13 Regression] ice in gfc_trans_pointer_assignment, at fortran/trans-expr.cc:10524

2024-05-08 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=113956

Paul Thomas  changed:

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution|--- |FIXED

--- Comment #9 from Paul Thomas  ---
Fixed on 13- through 15-branches. Thanks for the report.

Paul

[Bug fortran/114535] [13 regression] ICE with elemental finalizer

2024-05-08 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=114535

Paul Thomas  changed:

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution|--- |FIXED

--- Comment #7 from Paul Thomas  ---
Fixed on 13- through 15-branch. Thanks for the report.

Paul

[Bug fortran/113384] [14/15 Regression] FAIL: gfortran.dg/array_reference_1.f90 -O0 execution test

2024-05-08 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=113384

Paul Thomas  changed:

   What|Removed |Added

 CC||pault at gcc dot gnu.org

--- Comment #2 from Paul Thomas  ---

Hi David,

I don't see any errors for the four testcases that you have fingered - on:

Linux pc30.home 6.2.15-100.fc36.x86_64 #1 SMP PREEMPT_DYNAMIC Thu May 11
16:51:53 UTC 2023 x86_64 x86_64 x86_64 GNU/Linux

with:

GNU Fortran (GCC) 15.0.0 20240506 (experimental)

Regards

Paul

[Bug fortran/106999] [11/12/13 Regression] ICE tree check: expected record_type or union_type or qual_union_type, have function_type in gfc_class_data_get, at fortran/trans-expr.cc:233

2024-05-06 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=106999

Paul Thomas  changed:

   What|Removed |Added

 Resolution|--- |FIXED
 Status|NEW |RESOLVED

--- Comment #10 from Paul Thomas  ---
Fixed on 12-branch through to mainline. Thanks for the report.

Paul

[Bug fortran/112407] [13 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab

2024-05-06 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112407

Paul Thomas  changed:

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution|--- |FIXED

--- Comment #13 from Paul Thomas  ---
Fixed on all affected branches. Thanks for the report.

Paul

[Bug fortran/113885] [13 Regression] ice in gimplify_expr, at gimplify.cc:18658 with finalization

2024-05-06 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=113885

Paul Thomas  changed:

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution|--- |FIXED

--- Comment #6 from Paul Thomas  ---
Fixed on all affected branches. Thanks for the report.

Paul

[Bug fortran/110987] [13 Regression] Segmentation fault after finalization of a temporary variable

2024-05-06 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=110987

Paul Thomas  changed:

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution|--- |FIXED

--- Comment #12 from Paul Thomas  ---
Fixed on all affected branches. Thanks for the report.

Paul

[Bug fortran/114739] Ensure no IMPLICIT type errors appear when they should for inquiry references

2024-05-06 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=114739

Paul Thomas  changed:

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution|--- |FIXED

--- Comment #13 from Paul Thomas  ---
Backported to 12- and 13-branches.

Closing

Paul

[Bug fortran/114874] [14/15 Regression] ICE with select type, type is (character(*)), and substring

2024-05-04 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=114874

Paul Thomas  changed:

   What|Removed |Added

   Assignee|unassigned at gcc dot gnu.org  |pault at gcc dot gnu.org

--- Comment #7 from Paul Thomas  ---
Created attachment 58104
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=58104=edit
Fix for this PR

This seems to be the best fix. I have tried several different approaches in the
last two days but it has been an uphill struggle against the state of the block
namespaces at this stage of the compilation.

I'll think about it for another day or so before submitting.

Cheers

Paul

[Bug fortran/114874] [14/15 Regression] ICE with select type, type is (character(*)), and substring

2024-04-30 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=114874

--- Comment #6 from Paul Thomas  ---
(In reply to anlauf from comment #3)
> Adding Paul, hoping that he can tell what changed for SELECT TYPE recently.

Needless to say, the regression is caused by r14-9489.

I have a fix that regtests OK but causes a regression in an, as yet, untested
corner:

  subroutine foobar
type :: t
  integer :: i
end type
class(*), allocatable :: c
c = t (1)
select type (c)
  type is (t)
if (c(1)%i .ne. 1) stop 5 ! This now ICEs
end select
  end

My efforts have been interrupted by a failure of make-install, which seems to
happen every few months. I rather think that I should go back to magnetic
drives, rather than SSD.

It will now have to wait until tomorrow.

Paul

[Bug fortran/114874] [14/15 Regression] ICE with select type, type is (character(*)), and substring

2024-04-30 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=114874

--- Comment #5 from Paul Thomas  ---
(In reply to Paul Thomas from comment #4)
> (In reply to anlauf from comment #3)
> > Adding Paul, hoping that he can tell what changed for SELECT TYPE recently.
> 

When c is an array, it compiles and runs fine with mainline. The parse-tree
looks sensible too, unlike the scalar version.

program p
  implicit none
  class(*), allocatable :: c(:)
  c = ['abc']
  select type (c)
  type is (character(*))
 print *, c
 print *, c(1)(2:2)  ! Doesn't ICE
  end select
end

Paul

[Bug fortran/114874] [14/15 Regression] ICE with select type, type is (character(*)), and substring

2024-04-29 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=114874

Paul Thomas  changed:

   What|Removed |Added

 Ever confirmed|0   |1
   Last reconfirmed||2024-04-29
 Status|UNCONFIRMED |NEW

--- Comment #4 from Paul Thomas  ---
(In reply to anlauf from comment #3)
> Adding Paul, hoping that he can tell what changed for SELECT TYPE recently.

Hmmm! Nothing that I am aware of. I'll take a look tomorrow, The changes are
most strange.

Why do I get that horrible feeling?

Paul

[Bug fortran/114859] [14/15 Regression] Seeing new segmentation fault in same_type_as since r14-9752

2024-04-29 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=114859

--- Comment #16 from Paul Thomas  ---
Hi Jakub,

It's good news that the patch does indeed fix the full problem.

I committed to 15-branch with corrections to the ChangeLogs, as requested by
Mikael. What both of us missed was that I screwed up in the commit message by
using the wrong PR number; 114959 instead of 114859. The testcase also has the
wrong number, all of which came about because I initially named the working
directory incorrectly. I am trying to things in too much of a hurry late at
night!

I do apologise for giving you a bit of extra work in backporting to the RC.
I'll fix up 15-branch tomorrow morning.

Regards

Paul

[Bug fortran/114859] [14/15 Regression] Seeing new segmentation fault in same_type_as since r14-9752

2024-04-28 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=114859

Paul Thomas  changed:

   What|Removed |Added

  Attachment #58054|0   |1
is obsolete||

--- Comment #14 from Paul Thomas  ---
Created attachment 58063
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=58063=edit
Fix for this PR

Hi Jakub and Orion,

It took me a little while to reduce the problem to the testcase below. It goes
to the list as soon as regtesting is done.

The offending bit of code has been constrained even more than previously and
the return with empty_stmt (input_location) has been removed. It, apparently,
can make var_decls disappear.

Regards

Paul

diff --git a/gcc/fortran/trans-expr.cc b/gcc/fortran/trans-expr.cc
index 072adf3fe77..0280c441ced 100644
--- a/gcc/fortran/trans-expr.cc
+++ b/gcc/fortran/trans-expr.cc
@@ -1720,6 +1720,7 @@ gfc_trans_class_init_assign (gfc_code *code)
   gfc_se dst,src,memsz;
   gfc_expr *lhs, *rhs, *sz;
   gfc_component *cmp;
+  gfc_symbol *sym;

   gfc_start_block ();

@@ -1736,18 +1737,25 @@ gfc_trans_class_init_assign (gfc_code *code)
   /* The _def_init is always scalar.  */
   rhs->rank = 0;

-  /* Check def_init for initializers.  If this is a dummy with all default
- initializer components NULL, return NULL_TREE and use the passed value as
- required by F2018(8.5.10).  */
-  if (!lhs->ref && lhs->symtree->n.sym->attr.dummy)
+  /* Check def_init for initializers.  If this is an INTENT(OUT) dummy with
all
+ default initializer components NULL, return NULL_TREE and use the passed
+ value as required by F2018(8.5.10).  */
+  sym = code->expr1->expr_type == EXPR_VARIABLE ? code->expr1->symtree->n.sym
+   : NULL;
+  if (code->op != EXEC_ALLOCATE
+  && sym && sym->attr.dummy
+  && sym->attr.intent == INTENT_OUT)
 {
-  cmp = rhs->ref->next->u.c.component->ts.u.derived->components;
-  for (; cmp; cmp = cmp->next)
+  if (!lhs->ref && lhs->symtree->n.sym->attr.dummy)
{
- if (cmp->initializer)
-   break;
- else if (!cmp->next)
-   return build_empty_stmt (input_location);
+ cmp = rhs->ref->next->u.c.component->ts.u.derived->components;
+ for (; cmp; cmp = cmp->next)
+   {
+ if (cmp->initializer)
+   break;
+ else if (!cmp->next)
+   return NULL_TREE;
+   }
}
 }

diff --git a/gcc/fortran/trans-stmt.cc b/gcc/fortran/trans-stmt.cc
index c34e0b4c0cd..d355009fa5e 100644
--- a/gcc/fortran/trans-stmt.cc
+++ b/gcc/fortran/trans-stmt.cc
@@ -7262,11 +7262,12 @@ gfc_trans_allocate (gfc_code * code, gfc_omp_namelist
*omp_allocate)
{
  /* Use class_init_assign to initialize expr.  */
  gfc_code *ini;
- ini = gfc_get_code (EXEC_INIT_ASSIGN);
+ ini = gfc_get_code (EXEC_ALLOCATE);
  ini->expr1 = gfc_find_and_cut_at_last_class_ref (expr, true);
  tmp = gfc_trans_class_init_assign (ini);
  gfc_free_statements (ini);
- gfc_add_expr_to_block (, tmp);
+ if (tmp != NULL_TREE)
+   gfc_add_expr_to_block (, tmp);
}
   else if ((init_expr = allocate_get_initializer (code, expr)))
{
diff --git a/gcc/testsuite/gfortran.dg/pr114959.f90
b/gcc/testsuite/gfortran.dg/pr114959.f90
new file mode 100644
index 000..5cc3c052c1d
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/pr114959.f90
@@ -0,0 +1,33 @@
+! { dg-do compile }
+! { dg-options "-fdump-tree-original" }
+!
+! Fix the regression caused by r14-9752 (fix for PR112407)
+! Contributed by Orion Poplawski  
+! Problem isolated by Jakub Jelinek   and further
+! reduced here.
+!
+module m
+  type :: smoother_type
+integer :: i
+  end type
+  type :: onelev_type
+class(smoother_type), allocatable :: sm
+class(smoother_type), allocatable :: sm2a
+  end type
+contains
+  subroutine save_smoothers(level,save1, save2)
+Implicit None
+type(onelev_type), intent(inout) :: level
+class(smoother_type), allocatable , intent(inout) :: save1, save2
+integer(4) :: info
+
+info  = 0
+! r14-9752 causes the 'stat' declaration from the first ALLOCATE statement
+! to disappear, which triggers an ICE in gimplify_var_or_parm_decl. The
+! second ALLOCATE statement has to be present for the ICE to occur.
+allocate(save1, mold=level%sm,stat=info)
+allocate(save2, mold=level%sm2a,stat=info)
+  end subroutine save_smoothers
+end module m
+! Two 'stat's from the allocate statements and two from the final wrapper.
+! { dg-final { scan-tree-dump-times "integer\\(kind..\\) stat" 4 "original" }
}

[Bug fortran/114859] [14/15 Regression] Seeing new segmentation fault in same_type_as since r14-9752

2024-04-27 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=114859

Paul Thomas  changed:

   What|Removed |Added

 CC||anlauf at gmx dot de

--- Comment #13 from Paul Thomas  ---
(In reply to Jakub Jelinek from comment #12)
> There is still time, probably until Tuesday morning, so if it is committed
> say by Monday to trunk, it can be cherry-picked then.  I'd prefer to see the
> whole patch before acking it for 14.1, possibly even build a test rpm which
> could verify if the package now works again.

OK - I am on to it.

Thanks

Paul

@Harald - I will submit to the list a bit later on and, hopefully, will commit
tonight.

[Bug fortran/114859] [14/15 Regression] Seeing new segmentation fault in same_type_as since r14-9752

2024-04-27 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=114859

Paul Thomas  changed:

   What|Removed |Added

   Assignee|unassigned at gcc dot gnu.org  |pault at gcc dot gnu.org

--- Comment #11 from Paul Thomas  ---
Created attachment 58054
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=58054=edit
Fix for this PR

Hi Orion and Jakub,

Mea culpa, mea maxima culpa! I had totally overlooked the use of
gfc_trans_class_init_assign for application of 'mold' in class allocation.

  subroutine restore_smoothers(level,save1, save2,info)
snip
if (allocated(level%sm)) then
  if (info  == 0) call level%sm%free(info)
  if (info  == 0) deallocate(level%sm,stat=info)
end if
if (allocated(save1)) then
  if (info  == 0) allocate(level%sm,mold=save1,stat=info) ! Repeats
below...
  if (info == 0) call save1%clone_settings(level%sm,info)
end if
snip

the attached patch fixes both this problem and respects the standard for the
default initialization of INTENT(OUT) dummies. It regtests fine. A suitable
testcase is on its way.

@Jakub, As per your message of Fri Apr 26 11:03:31, I hope that the patch can
find its way to the 14.1 release candidate.

Regards

Paul

[Bug fortran/61527] [11/12/13/14 Regression] [OOP] class/extends, multiple generic assignment, accept invalid

2024-04-26 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=61527

Paul Thomas  changed:

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution|--- |FIXED
 CC||pault at gcc dot gnu.org

--- Comment #18 from Paul Thomas  ---
>From at least 7.4.1 20191027 on, gfortran gives the correct result and detects
ambiguity for both cases. NAG and Intel agree.

Closing as resolved.

Paul

[Bug fortran/84868] [11/12/13/14 Regression] ICE in gfc_conv_descriptor_offset, at fortran/trans-array.c:208

2024-04-26 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84868

Paul Thomas  changed:

   What|Removed |Added

   Assignee|unassigned at gcc dot gnu.org  |pault at gcc dot gnu.org
 CC||pault at gcc dot gnu.org

--- Comment #14 from Paul Thomas  ---
(In reply to G. Steinmetz from comment #0)
> Changed between 20161204 and 20161211 :
> 
> 
> $ cat z1.f90
> module m
>character(:), allocatable :: c
> contains
>function f(n) result(z)
>   character, parameter :: c(3) = ['x', 'y', 'z']
>   integer, intent(in) :: n
>   character(len_trim(c(n))) :: z
>   z = c(n)
>end
> end
> program p
>use m
>print *, f(2)
> end
> 
> 
> $ gfortran-7-20161204 -c z1.f90
> $
> $ gfortran-8-20180311 -c z1.f90
> z1.f90:13:0:
> 
> print *, f(2)
> 
> internal compiler error: in gfc_conv_descriptor_offset, at
> fortran/trans-array.c:208
> 0x74e222 gfc_conv_descriptor_offset
> ../../gcc/fortran/trans-array.c:208
> 0x75349c gfc_conv_descriptor_offset_get(tree_node*)
> ../../gcc/fortran/trans-array.c:220
> 0x75349c gfc_conv_array_offset(tree_node*)
> ../../gcc/fortran/trans-array.c:2967
> 0x75349c gfc_conv_array_ref(gfc_se*, gfc_array_ref*, gfc_expr*, locus*)
> ../../gcc/fortran/trans-array.c:3575
> 0x780ddd gfc_conv_variable
> ../../gcc/fortran/trans-expr.c:2737
> 0x77db02 gfc_conv_expr(gfc_se*, gfc_expr*)
> ../../gcc/fortran/trans-expr.c:7926
> 0x78a98c gfc_conv_intrinsic_function_args
> ../../gcc/fortran/trans-intrinsic.c:223
> 0x79dc3d gfc_conv_intrinsic_len_trim
> ../../gcc/fortran/trans-intrinsic.c:6248
> 0x79dc3d gfc_conv_intrinsic_function(gfc_se*, gfc_expr*)
> ../../gcc/fortran/trans-intrinsic.c:9134
> 0x77d545 gfc_conv_function_expr
> ../../gcc/fortran/trans-expr.c:6784
> 0x77dae2 gfc_conv_expr(gfc_se*, gfc_expr*)
> ../../gcc/fortran/trans-expr.c:7918
> 0x77fa8a gfc_apply_interface_mapping(gfc_interface_mapping*, gfc_se*,
> gfc_expr*)
> ../../gcc/fortran/trans-expr.c:4409
> 0x77b6f7 gfc_conv_procedure_call(gfc_se*, gfc_symbol*, gfc_actual_arglist*,
> gfc_expr*, vec*)
> ../../gcc/fortran/trans-expr.c:5970
> 0x77d59c gfc_conv_function_expr
> ../../gcc/fortran/trans-expr.c:6808
> 0x77dae2 gfc_conv_expr(gfc_se*, gfc_expr*)
> ../../gcc/fortran/trans-expr.c:7918
> 0x7843aa gfc_conv_expr_reference(gfc_se*, gfc_expr*)
> ../../gcc/fortran/trans-expr.c:8018
> 0x7a3d56 gfc_trans_transfer(gfc_code*)
> ../../gcc/fortran/trans-io.c:2585
> 0x749ec7 trans_code
> ../../gcc/fortran/trans.c:2044
> 0x7a1807 build_dt
> ../../gcc/fortran/trans-io.c:2027
> 0x749ee7 trans_code
> ../../gcc/fortran/trans.c:2016

This, I believe, was commit 345bd7ebbb38f0e1d5acf33ab3f680111cfa7871 where
LEN_TRIM was introduced to interface mapping on 2016-12-09 for pr44265.
Removing the chunk concerned does not fix the problem.

I have stared at this for ages. For reasons that I cannot see, the use
associated version of 'c' is being used, so the interface mapping has failed.

I will come back to this.

Paul

[Bug fortran/102620] [12 Regression] ICE in gfc_get_array_span, at fortran/trans-array.c:865 since r12-1233-gd514626ee2566c68

2024-04-25 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=102620

--- Comment #11 from Paul Thomas  ---
(In reply to anlauf from comment #10)
> (In reply to Paul Thomas from comment #9)
> > (In reply to anlauf from comment #8)
> > > I get the same behavior at r13-8559 as 14-mainline.  There seems to be
> > > another commit that fixed it independently.
> > > 
> > > Removing 13-branch from the regression list.
> > 
> > Mark as fixed or backport fixes?
> 
> Either I did something wrong, or the bug reappeared on 13-branch...
> 
> Anyway, I tried backporting Andre's patch to 13- and 12-branch.
> Works fine and regtests fine.
> 
> How to proceed?
> 
> I can push those changes, so that we are finally done with this PR.

Hi Harald,

It would be splendid if you would backport the patch. In the last week or so, I
have built up quite a list of backports to do, which I will attend to over the
weekend.

We are down from 105 regressions on 26th March to 94 now, of which 13 are now
fixed on mainline. Since there are still some P1 regressions, I have been
prowling around looking for more low hanging edibles while there is still time.

Regards

Paul

[Bug fortran/113885] [13 Regression] ice in gimplify_expr, at gimplify.cc:18658 with finalization

2024-04-25 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=113885

Paul Thomas  changed:

   What|Removed |Added

Summary|[13/14 Regression] ice in   |[13 Regression] ice in
   |gimplify_expr, at   |gimplify_expr, at
   |gimplify.cc:18658 with  |gimplify.cc:18658 with
   |finalization|finalization

--- Comment #4 from Paul Thomas  ---
Updated summary

Paul

[Bug fortran/99183] [11 Regression] Incompatible Runtime types

2024-04-25 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=99183

Paul Thomas  changed:

   What|Removed |Added

 Resolution|--- |FIXED
 Status|NEW |RESOLVED

--- Comment #9 from Paul Thomas  ---

> As soon as regtesting is finished, I will push and close.
> 
> Cheers
> 
> Paul

The original PR for this was 102745, which was also fixed on 11-branch :-)

Closing as RESOLVED/FIXED

Paul

[Bug fortran/95682] [11/12 Regression] Default assignment fails with allocatable array of deferred-length strings

2024-04-25 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=95682

Paul Thomas  changed:

   What|Removed |Added

 Resolution|--- |WONTFIX
 CC||pault at gcc dot gnu.org
 Status|NEW |RESOLVED

--- Comment #8 from Paul Thomas  ---
(In reply to anlauf from comment #2)
> Adding some printout after initializing the t1%x(:),
> 
>   do i = 1, size(t1%x)
>  print *, len_trim (t1%x(i)), t1%x(i)
>   end do
> 
> I get for gcc-8:
> 
>5 three 
>5 three 
>5 three 
> 
> and for 9,10,11:
> 
>3 one   
>3 two   
>5 three 
> 
> That's not a typical regression, but rather wrong code replaced by other
> wrong
> code.

Since this was not really a regression, as you remark, and the testcase works
correctly from 12-branch through mainline, I am closing as a WONTFIX.

Paul

[Bug fortran/99183] [11 Regression] Incompatible Runtime types

2024-04-25 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=99183

Paul Thomas  changed:

   What|Removed |Added

 CC||pault at gcc dot gnu.org

--- Comment #8 from Paul Thomas  ---
(In reply to Dominique d'Humieres from comment #4)
> > This seems to have been fixed between r12-4097 and r12-4638.
> 
> Duplicate of pr102745, fixed by r12-4464?

Yes, indeed. It applies cleanly to 11-branch and fixes the problem.

As soon as regtesting is finished, I will push and close.

Cheers

Paul

[Bug fortran/89462] [11/12/13 Regression] gfortran loops in code generation

2024-04-25 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89462

Paul Thomas  changed:

   What|Removed |Added

   Assignee|unassigned at gcc dot gnu.org  |pault at gcc dot gnu.org

--- Comment #16 from Paul Thomas  ---
Taking to remind myself to backport.

Paul

[Bug fortran/100815] [11 Regression] Segfault assigning to scalar allocatable polymorphic LHS since r11-6253-gce8dcc9105cbd404

2024-04-25 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=100815

Paul Thomas  changed:

   What|Removed |Added

 Resolution|--- |WONTFIX
 Status|NEW |RESOLVED

--- Comment #9 from Paul Thomas  ---
(In reply to Paul Thomas from comment #6)
> (In reply to Martin Liška from comment #5)
> > It's fixed on master with r12-3897-g00f6de9c691195.
> 
> Many thanks, Martin.
> 
> I'll try to apply it to 11-branch, if for no other reason than to see if it
> does so cleanly. Tobias must have thought that it was too invasive to
> backport.
> 

I think that we should take this view, given the imminent opening of 15-branch.

Cheers

Paul

[Bug fortran/102620] [12 Regression] ICE in gfc_get_array_span, at fortran/trans-array.c:865 since r12-1233-gd514626ee2566c68

2024-04-25 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=102620

Paul Thomas  changed:

   What|Removed |Added

 CC||pault at gcc dot gnu.org

--- Comment #9 from Paul Thomas  ---
(In reply to anlauf from comment #8)
> I get the same behavior at r13-8559 as 14-mainline.  There seems to be
> another commit that fixed it independently.
> 
> Removing 13-branch from the regression list.

Mark as fixed or backport fixes?

Cheers

Paul

[Bug fortran/104717] [11 Regression] ICE: verify_ssa failed (Error: type mismatch between an SSA_NAME and its symbol)

2024-04-25 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=104717

Paul Thomas  changed:

   What|Removed |Added

 CC||pault at gcc dot gnu.org

--- Comment #14 from Paul Thomas  ---
(In reply to GCC Commits from comment #10)

Hi Jakub and Thomas,

Are you planning to backport to 11-branch, or can this be closed?

Cheers

Paul

[Bug fortran/104391] [11 Regression] bind(C) and allocatable or pointer attribute don't work

2024-04-25 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=104391

Paul Thomas  changed:

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution|--- |FIXED

--- Comment #6 from Paul Thomas  ---
(In reply to Martin Liška from comment #2)
> Fixed on master with r12-2511-g0cbf03689e3e7d9d, started with
> r9-5372-gbbf18dc5d248a79a.

Yes, indeed.

Thanks, Martin.

[Bug fortran/89462] [11/12/13 Regression] gfortran loops in code generation

2024-04-25 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89462

Paul Thomas  changed:

   What|Removed |Added

Summary|[11/12/13/14 Regression]|[11/12/13 Regression]
   |gfortran loops in code  |gfortran loops in code
   |generation  |generation
 CC||pault at gcc dot gnu.org

--- Comment #15 from Paul Thomas  ---
Fixed on mainline, so changing summary. Will backport in a couple of weeks.

Paul

[Bug fortran/93678] [11/12/13 Regression] ICE with TRANSFER and typebound procedures

2024-04-25 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=93678

Paul Thomas  changed:

   What|Removed |Added

Summary|[11/12/13/14 Regression]|[11/12/13 Regression] ICE
   |ICE with TRANSFER and   |with TRANSFER and typebound
   |typebound procedures|procedures

--- Comment #16 from Paul Thomas  ---
Fixed on mainline, so changing summary. Will backport in a couple of weeks.

Paul

[Bug fortran/114815] [PDT] internal compiler error: Segmentation fault - on creating type with len parameter and dependent on it character array

2024-04-24 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=114815

Paul Thomas  changed:

   What|Removed |Added

 CC||pault at gcc dot gnu.org

--- Comment #3 from Paul Thomas  ---
(In reply to anlauf from comment #2)
> The code in comment#0 is invalid.
> 
> Intel:
> 
> pr114815.f90(5): error #8737: For a default initialized component every type
> parameter and array bound must be a constant expression.   [GENDERS]
> end type Student_Group
> ^
> 
> NAG:
> 
> Error: pr114815.f90, line 4: Type STUDENT_GROUP default-initialised
> component GENDERS has a non-constant array bound
> Errors in declarations, no further processing for LAB_1_4
> 
> 
> When commenting the default initialization, the code compiles with gfortran.

My first project once 14-branch is released will be to put PDTs to rights.
Unfortunately, the representation is plain wrong and I don't see any point in
cosmetic fixes until that is put right.

Sorry

Paul

[Bug fortran/93678] [11/12/13/14 Regression] ICE with TRANSFER and typebound procedures

2024-04-24 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=93678

Paul Thomas  changed:

   What|Removed |Added

   Assignee|unassigned at gcc dot gnu.org  |pault at gcc dot gnu.org
 CC||pault at gcc dot gnu.org

--- Comment #14 from Paul Thomas  ---
Created attachment 58026
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=58026=edit
Fix for this PR

I'll package it all up for the list in the next 24 hours. Regtests OK, the
testcase of comment 1 compiles and this runs fine:

! { dg-do compile }
! Test the fix for PR93678 in which the charlen for the 'unpackbytes'
! vtable field was incomplete and caused the ICE as indicated.
! Contributed by Luis Kornblueh  
!
! The testcase was reduced by various gfortran regulars.
module mo_a
  implicit none
  type t_b
integer :: i
  contains
procedure :: unpackbytes => b_unpackbytes
  end type t_b
contains
  function b_unpackbytes (me) result (res)
class(t_b), intent(inout) :: me
character :: res(1)
res = char (me%i)
  end function b_unpackbytes
  subroutine b_unpackint (me, c)
class(t_b), intent(inout) :: me
character, intent(in) :: c
!   print *, b_unpackbytes (me) ! ok
if (any (me% unpackbytes () .ne. c)) stop 1 ! ICEd here
  end subroutine b_unpackint
end module mo_a

  use mo_a
  class(t_b), allocatable :: z
  allocate (z, source = t_b(97))
  call b_unpackint (z, "a")
end

[Bug fortran/71703] [11 Regression] [OOP] ICE in wide_int_to_tree, at tree.c:1488

2024-04-23 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=71703

Paul Thomas  changed:

   What|Removed |Added

 Resolution|--- |FIXED
 Status|NEW |RESOLVED
 CC||pault at gcc dot gnu.org

--- Comment #20 from Paul Thomas  ---
All the failing testcases posted in this PR now compile and run correctly.

Many thanks once again, Gerhard.

Paul

[Bug fortran/106999] [11/12/13 Regression] ICE tree check: expected record_type or union_type or qual_union_type, have function_type in gfc_class_data_get, at fortran/trans-expr.cc:233

2024-04-23 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=106999

Paul Thomas  changed:

   What|Removed |Added

Summary|[11/12/13/14 Regression]|[11/12/13 Regression] ICE
   |ICE tree check: expected|tree check: expected
   |record_type or union_type   |record_type or union_type
   |or qual_union_type, have|or qual_union_type, have
   |function_type in|function_type in
   |gfc_class_data_get, at  |gfc_class_data_get, at
   |fortran/trans-expr.cc:233   |fortran/trans-expr.cc:233

--- Comment #7 from Paul Thomas  ---
Needs backporting. Changed summary.

[Bug fortran/110987] [13 Regression] Segmentation fault after finalization of a temporary variable

2024-04-23 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=110987

Paul Thomas  changed:

   What|Removed |Added

Summary|[13/14 Regression]  |[13 Regression]
   |Segmentation fault after|Segmentation fault after
   |finalization of a temporary |finalization of a temporary
   |variable|variable

--- Comment #10 from Paul Thomas  ---
Needs backporting. Summary changed.

[Bug fortran/112407] [13 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab

2024-04-23 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112407

Paul Thomas  changed:

   What|Removed |Added

Summary|[13/14 Regression] Fix for  |[13 Regression] Fix for
   |PR37336 triggers an ICE in  |PR37336 triggers an ICE in
   |gfc_format_decoder while|gfc_format_decoder while
   |constructing a vtab |constructing a vtab

--- Comment #11 from Paul Thomas  ---
Needs backporting. Summary changed.

[Bug fortran/114739] Ensure no IMPLICIT type errors appear when they should for inquiry references

2024-04-23 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=114739

Paul Thomas  changed:

   What|Removed |Added

Summary|[14 Regression] ice in  |Ensure no IMPLICIT type
   |gfc_find_derived_types, at  |errors appear when they
   |fortran/symbol.cc:2458  |should for inquiry
   ||references

--- Comment #10 from Paul Thomas  ---
Changed the summary line

[Bug fortran/102597] ICE in gfc_get_extern_function_decl, at fortran/trans-decl.c:2243 since r8-3365-gb89a63b916340ef2

2024-04-22 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=102597

Paul Thomas  changed:

   What|Removed |Added

 Resolution|--- |FIXED
 Status|WAITING |RESOLVED

--- Comment #3 from Paul Thomas  ---
Fails with 11.2.1 20210728 and is OK with 12.2.1 20230321.

Thanks for the report Gerhard. I think that we can shut this one down.

Paul

[Bug fortran/103471] Missed no IMPLICIT type errors

2024-04-21 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103471

Paul Thomas  changed:

   What|Removed |Added

Summary|[11/12/13/14 Regression]|Missed no IMPLICIT type
   |ICE in  |errors
   |gfc_typenode_for_spec, at   |
   |fortran/trans-types.c:1114  |

--- Comment #12 from Paul Thomas  ---
The regression has been cured in the above commit and some of the missed error
messages have been fixed.

Compared with the submission to the list and discussed with Harald Anlauf, an
extra chunk has been added in resolve.cc(resolve_actual_arglist) to catch
untyped actual arguments.

See the testcase commented out line for an example interference between
different statements with untyped symbols.

I am keeping this one open having changed the summary.

Paul

[Bug fortran/114739] [14 Regression] ice in gfc_find_derived_types, at fortran/symbol.cc:2458

2024-04-19 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=114739

--- Comment #9 from Paul Thomas  ---

> The incorrect errors will have to be fixed on 13-branch at very least.
> Unfortunately, this is not a question of using a backport but I will get
> onto it right away.
> 


I have applied the backport manually and it works fine in eliminating the
incorrect error. I'll apply to 12- and 13-branches in a couple of weeks.

Cheers

Paul

[Bug fortran/114739] [14 Regression] ice in gfc_find_derived_types, at fortran/symbol.cc:2458

2024-04-19 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=114739

--- Comment #8 from Paul Thomas  ---
Thanks for the report. Fixed on mainline.

The incorrect errors will have to be fixed on 13-branch at very least.
Unfortunately, this is not a question of using a backport but I will get onto
it right away.

Regards

Paul

[Bug fortran/103471] [11/12/13/14 Regression] ICE in gfc_typenode_for_spec, at fortran/trans-types.c:1114

2024-04-19 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103471

--- Comment #10 from Paul Thomas  ---
(In reply to Paul Thomas from comment #9)
> > This looks more user friendly.
> 
> Also true. I have put it on to regtest but I think that it might be a good
> idea to understand how the symbol evades resolution :-)
> 
> Paul

It regtests OK.

Paul

[Bug fortran/103471] [11/12/13/14 Regression] ICE in gfc_typenode_for_spec, at fortran/trans-types.c:1114

2024-04-19 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103471

--- Comment #9 from Paul Thomas  ---

> This looks more user friendly.

Also true. I have put it on to regtest but I think that it might be a good idea
to understand how the symbol evades resolution :-)

Paul

[Bug fortran/103471] [11/12/13/14 Regression] ICE in gfc_typenode_for_spec, at fortran/trans-types.c:1114

2024-04-19 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103471

--- Comment #8 from Paul Thomas  ---

> This looks more user friendly.

Also true. I have put it on to regtest but I think that it might be a good idea
to understand how the symbol evades resolution :-)

Paul

[Bug fortran/114739] [14 Regression] ice in gfc_find_derived_types, at fortran/symbol.cc:2458

2024-04-17 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=114739

Paul Thomas  changed:

   What|Removed |Added

   Assignee|unassigned at gcc dot gnu.org  |pault at gcc dot gnu.org

--- Comment #6 from Paul Thomas  ---
Hi David and Harald,

Thanks for the heads up.

I am within minutes of posting a fix on the list.

Paul

[Bug fortran/103312] [11/12/13/14 Regression] ICE in gfc_find_component since r9-1098-g3cf89a7b992d483e

2024-04-17 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103312

Paul Thomas  changed:

   What|Removed |Added

 CC||pault at gcc dot gnu.org
   Assignee|unassigned at gcc dot gnu.org  |pault at gcc dot gnu.org

--- Comment #6 from Paul Thomas  ---
Created attachment 57969
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=57969=edit
Partial fix for the PR

The supplied testcase generates completely blank derived type symbols for the
_vptr component of 'this' in 'func'. The chunk in resolve.cc fixes that.

The rest of the patch allows the full testcase below to blast through to
translation, where it dies in trans-decl.cc - again with blanks symbols in the
default initializer this time.

Of the compilers to which I have access, only NAG succeeds with the full
testcase. If this%size() is replaced with a constant expression or an integer
dummy argument, all compilers succeed, including current versions of gfortran.

I have taken it but need to get on with daytime work for a few days.

Paul

module example

  type, abstract :: foo
integer :: i
  contains
procedure(foo_size), deferred :: size
procedure(foo_func), deferred :: func
  end type

  interface
function foo_func (this) result (string)
  import :: foo
  class(foo) :: this
  character(this%size()) :: string
end function
pure integer function foo_size (this)
  import foo
  class(foo), intent(in) :: this
end function
  end interface

end module

module extension
  use example
  implicit none
  type, extends(foo) :: bar
!integer :: i
  contains
procedure :: size
procedure :: func
  end type

contains
pure integer function size (this)
  class(bar), intent(in) :: this
  size = this%i
end function
function func (this) result (string)
  class(bar) :: this
  character(this%size()) :: string
  string = repeat ("x", len (string))
end function

end module

  use example
  use extension
  type(bar) :: a
  a%i = 5
  print *, a%func()
end

[Bug fortran/103471] [11/12/13/14 Regression] ICE in gfc_typenode_for_spec, at fortran/trans-types.c:1114

2024-04-11 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103471

Paul Thomas  changed:

   What|Removed |Added

 CC||pault at gcc dot gnu.org

--- Comment #6 from Paul Thomas  ---
The current mainline and 13-branches now power through to the fatal error at
trans-decl.cc:1800.

Paul

[Bug fortran/105168] [11/12/13/14 Regression] ICE in gfc_maybe_dereference_var, at fortran/trans-expr.cc:2870 since r9-3522-gd0477233215e37de

2024-04-11 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=105168

Paul Thomas  changed:

   What|Removed |Added

 CC||pault at gcc dot gnu.org

--- Comment #6 from Paul Thomas  ---
(In reply to Martin Liška from comment #2)
> Started with r9-3522-gd0477233215e37de.

Hi Martin,

Reverting this patch has no effect on the ICE.

Regards

Paul

[Bug fortran/113363] ICE on ASSOCIATE and unlimited polymorphic function

2024-04-06 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=113363

--- Comment #7 from Paul Thomas  ---
Created attachment 57892
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=57892=edit
Fix for this PR

The attachment has two fixes for the PR :-)

The first chunk in trans-array.cc is an  alternative to the direct, rather
brutal chunk in trans-stmt.cc. The latter, though, isolates the fix to allocate
statements. I am not entirely sure which is better.

It needs some comments and a proper testcase.

Cheers

Paul

[Bug fortran/87477] [meta-bug] [F03] issues concerning the ASSOCIATE statement

2024-04-04 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87477
Bug 87477 depends on bug 113363, which changed state.

Bug 113363 Summary: ICE on ASSOCIATE and unlimited polymorphic function
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=113363

   What|Removed |Added

 Status|RESOLVED|WAITING
 Resolution|FIXED   |---

[Bug fortran/113363] ICE on ASSOCIATE and unlimited polymorphic function

2024-04-04 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=113363

Paul Thomas  changed:

   What|Removed |Added

 Status|RESOLVED|WAITING
 Resolution|FIXED   |---

--- Comment #5 from Paul Thomas  ---
(In reply to anlauf from comment #4)
> This PR has been fixed as part of the large commit r14-9489-g3fd46d859cda10 .

Not here. As far as I can tell the results remain exactly the same for both
character and numeric results from 'foo'.

Is it possible that there is a patch lurking in your tree that has fixed it?

Cheers

Paul

[Bug fortran/113956] [13/14 Regression] ice in gfc_trans_pointer_assignment, at fortran/trans-expr.cc:10524

2024-04-03 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=113956

Paul Thomas  changed:

   What|Removed |Added

   Assignee|unassigned at gcc dot gnu.org  |pault at gcc dot gnu.org

--- Comment #6 from Paul Thomas  ---
I'll take it.

Paul

[Bug fortran/114535] [13/14 regression] ICE with elemental finalizer

2024-04-01 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=114535

--- Comment #4 from Paul Thomas  ---
Created attachment 57839
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=57839=edit
"Fix" for this PR

Even though no entities of type 'vs' are being referenced in subroutine iss,
gfortran currently feels the need to generate a final wrapper for it. The
comment in the patch explains what is happening but not why. I suspect that the
evil is being done somewhere in resolve.cc and will investigate in another
session.

Note the comments in the testcase below:

module d
  implicit none
contains
  function en() result(dd)
use :: iv
implicit none
type(vs) :: dd
dd%i = 1
  end function en
end module d

! Comment out line 1 and all brands complain that 'vs' is an undefined type
! Comment out line 1 and line 2 allows compilation to proceed (with fix for
gfortran)
module ni
  implicit none
contains
  subroutine iss()
use :: iv! line 1
use :: d
implicit none
type(vs) :: ans; ans = en(); print *, ctr, ans%i ! line 2
  end subroutine iss
end module ni

  use ni
  call iss()
  call iss()
!  print *, ctr
end

[Bug fortran/106987] [11/12/13/14 Regression] ICE in simplify_intrinsic_op, at fortran/expr.cc:1305

2024-03-31 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=106987

Paul Thomas  changed:

   What|Removed |Added

 CC||pault at gcc dot gnu.org
   Assignee|unassigned at gcc dot gnu.org  |anlauf at gcc dot 
gnu.org

--- Comment #5 from Paul Thomas  ---
Hi Harald,

I am pinning this one on you since it needs backporting to 13-branch, at least.
It also keeps the audit trail clean.

Cheers

Paul

[Bug fortran/106999] [11/12/13/14 Regression] ICE tree check: expected record_type or union_type or qual_union_type, have function_type in gfc_class_data_get, at fortran/trans-expr.cc:233

2024-03-31 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=106999

Paul Thomas  changed:

   What|Removed |Added

 CC||pault at gcc dot gnu.org
   Assignee|unassigned at gcc dot gnu.org  |pault at gcc dot gnu.org

--- Comment #5 from Paul Thomas  ---
Created attachment 57838
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=57838=edit
Fix for this PR

Thanks for the report. The attached does what is required, I believe. It is
regtesting as I write.

Paul

[Bug fortran/114535] [13/14 regression] ICE with elemental finalizer

2024-03-31 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=114535

Paul Thomas  changed:

   What|Removed |Added

Summary|ICE with elemental  |[13/14 regression] ICE with
   |finalizer   |elemental finalizer

--- Comment #2 from Paul Thomas  ---
It seems to be OK with 12-branch.

It's not unlike some of the problems with your smart pointer work.

I have a couple more regressions to take care of and the, I promise, I will
turn to this one.

Paul

[Bug fortran/114535] ICE with elemental finalizer

2024-03-31 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=114535

Paul Thomas  changed:

   What|Removed |Added

 CC||pault at gcc dot gnu.org
   Assignee|unassigned at gcc dot gnu.org  |pault at gcc dot gnu.org
 Status|UNCONFIRMED |NEW
 Ever confirmed|0   |1
   Last reconfirmed||2024-03-31

--- Comment #1 from Paul Thomas  ---
Hi Andrew,

Confirmed.

A work around is:

module ni
  implicit none
contains
  subroutine iss()
use :: iv  ! Implies something is awry in module.cc
use :: d
return
  end subroutine iss
end module ni

Thanks for the report. I'll take it but it has been a while since I looked at
module.cc.

Regards

Paul

[Bug fortran/107426] [12/13/14 Regression] ICE in gfc_compare_derived_types, at fortran/interface.cc:636

2024-03-30 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=107426

Paul Thomas  changed:

   What|Removed |Added

   Assignee|unassigned at gcc dot gnu.org  |mikael at gcc dot 
gnu.org
 CC||pault at gcc dot gnu.org

--- Comment #9 from Paul Thomas  ---
Hi Mikael,

I have assigned the PR to you since you have fixed it on mainline. I presume
that you will backport?

Regards

Paul

[Bug fortran/112407] [13/14 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab

2024-03-30 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112407

--- Comment #9 from Paul Thomas  ---
(In reply to Paul Thomas from comment #8)
> Created attachment 57835 [details]
> An alternative fix for the PR
> 
> Hi Tomas,
> 
> Would you prefer the compiler to give warning rather than letting the
> possible recursion to pass by silently?
> 
> f951: Warning: Non-RECURSIVE procedure ‘newcopyother’ from module
> ‘ftldynarrayintmodule’ is  possibly calling itself recursively in procedure
> ‘newcopyother’.  Declare it RECURSIVE or use ‘-frecursive’
> 
> Cheers
> 
> Paul

After reflection, I have answered the question myself. The other part of the
patch in resolve.cc should ensure that the recursion is detected in the module
compilation.

Paul

[Bug fortran/113956] [13/14 Regression] ice in gfc_trans_pointer_assignment, at fortran/trans-expr.cc:10524

2024-03-29 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=113956

--- Comment #3 from Paul Thomas  ---
(In reply to anlauf from comment #2)
> Reduced testcase:
> 
> subroutine test_array_char(p, x)
>   character(*), target  :: x(100)
>   character(:), pointer :: p(:)
>   p => x
> end subroutine
> 
> 
> We hit an assert that can be worked around with the following patch:
> 
> diff --git a/gcc/fortran/trans-expr.cc b/gcc/fortran/trans-expr.cc
> index d21e3956d6e..fa31f950363 100644
> --- a/gcc/fortran/trans-expr.cc
> +++ b/gcc/fortran/trans-expr.cc
> @@ -10534,12 +10535,9 @@ gfc_trans_pointer_assignment (gfc_expr * expr1,
> gfc_expr * expr2)
>   {
> 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;
> - }
> +   if (psym->ts.type == BT_CHARACTER
> +   && 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;
> 
> 
> This fragment was touched by Paul's fix for pr67740 (r14-4583), so adding
> him.
> 
> @Paul: can you please have a look?

I can see why the assert is there but it is manifestly wrong for both the
assumed length target and a constant length. I was thrown a bit by the distros
nulling out the asserts so that it compiled just fine with the system gfortran.

Your patch is perfect :- This compiles and runs correctly:
module m
contains
  subroutine test_array_char(p, x)
character(*), target  :: x(:)
character(:), pointer :: p(:)
p => x
  end subroutine
end module

  use m
  character(:), allocatable, target :: chr(:)
  character(:), pointer :: p(:)
  chr = ["ab","cd"]
  call test_array_char (p, chr)
  print '(l2,i4,2a4)', loc(chr) == loc(p), len(p), p
end

Cheers

Paul

[Bug fortran/112407] [13/14 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab

2024-03-29 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112407

--- Comment #8 from Paul Thomas  ---
Created attachment 57835
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=57835=edit
An alternative fix for the PR

Hi Tomas,

Would you prefer the compiler to give warning rather than letting the possible
recursion to pass by silently?

f951: Warning: Non-RECURSIVE procedure ‘newcopyother’ from module
‘ftldynarrayintmodule’ is  possibly calling itself recursively in procedure
‘newcopyother’.  Declare it RECURSIVE or use ‘-frecursive’

Cheers

Paul

[Bug fortran/112407] [13/14 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab

2024-03-29 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112407

--- Comment #7 from Paul Thomas  ---
Created attachment 57833
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=57833=edit
A patch that fixes all the issues in this PR

I apologise for taking so long to return to this problem. Daytime work and a
long trip to Australia have removed my gaze from the ball.

At this stage of the release cycle, I have decided to go for the safe, "hacky"
fix of your problem.

In the course of the investigation, I found that recursion involving type bound
procedures was not being detected and that class objects with NULL default
initializers were being applied to intent(OUT) dummies. These are both fixed.

I will submit to the list as soon as I have written the ChangeLogs.

Regards

Paul

[Bug fortran/110987] [13/14 Regression] Segmentation fault after finalization of a temporary variable

2024-03-28 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=110987

Paul Thomas  changed:

   What|Removed |Added

   Assignee|unassigned at gcc dot gnu.org  |pault at gcc dot gnu.org

--- Comment #8 from Paul Thomas  ---
Since I just submitted the fix for this and pr113885, I had better take it :-)

Paul

[Bug fortran/103716] [11/12/13 Regression] ICE in gimplify_expr, at gimplify.c:15964 since r9-3803-ga5fbc2f36a291cbe

2024-03-28 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103716

Paul Thomas  changed:

   What|Removed |Added

 Resolution|--- |FIXED
 Status|ASSIGNED|RESOLVED

--- Comment #10 from Paul Thomas  ---
Fixed on 13- and 14-branches. Closing.

Thanks for the report

Paul

[Bug fortran/113885] [13/14 Regression] ice in gimplify_expr, at gimplify.cc:18658 with finalization

2024-03-27 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=113885

Paul Thomas  changed:

   What|Removed |Added

   Assignee|unassigned at gcc dot gnu.org  |pault at gcc dot gnu.org

--- Comment #2 from Paul Thomas  ---
Created attachment 57820
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=57820=edit
Draft fix for this PR

Many thanks for the report.

The attachment needs some cleaning up and testing with other variants that
might generate the problem.

In fact, this is a double regression since the testcase below does not give the
right result for 'x' in the calls to test1 and test2.

The first regression is associated with the derived type having zero components
messing up the finalization calls. Strictly, this is not a regression since the
older versions of gfortran did not attempt the finalization.

The second regression is due to the attempt to place finalization calls in the
correct place relative to the evaluation of the rhs and the assignment to the
lhs. This is the cause of the incorrect results for the testcase below. I
believe that the correct output is:
after test1 x =2   3
no. final calls =4
after test2 x =6   8
no. final calls =   12

nagfor agrees but ifort gives 3 and 8 respectively for the no. of
finalizations.

To my astonishment, given the current stage of the fix, it even regtests OK :-)

Paul

module types
  type t
 integer :: i
   contains
 final :: finalize
  end type t
  integer :: ctr = 0
contains
  impure elemental subroutine finalize(x)
type(t), intent(inout) :: x
ctr = ctr + 1
  end subroutine finalize
end module types

impure elemental function elem(x)
  use types
  type(t), intent(in) :: x
  type(t) :: elem
  elem%i = x%i + 1
end function elem

impure elemental function elem2(x, y)
  use types
  type(t), intent(in) :: x, y
  type(t) :: elem2
  elem2%i = x%i + y%i
end function elem2

subroutine test1(x)
  use types
  interface
 impure elemental function elem(x)
   use types
   type(t), intent(in) :: x
   type(t) :: elem
 end function elem
  end interface
  type(t) :: x(:)
  x = elem(x)
end subroutine test1

subroutine test2(x)
  use types
  interface
 impure elemental function elem(x)
   use types
   type(t), intent(in) :: x
   type(t) :: elem
 end function elem
 impure elemental function elem2(x, y)
   use types
   type(t), intent(in) :: x, y
   type(t) :: elem2
 end function elem2
  end interface
  type(t) :: x(:)
  x = elem2(elem(x), elem(x))
end subroutine test2

program test113885
  use types
  interface
subroutine test1(x)
  use types
  type(t) :: x(:)
end subroutine
subroutine test2(x)
  use types
  type(t) :: x(:)
end subroutine
  end interface
  type(t) :: x(2) = [t(1),t(2)]
  call test1 (x)
  print "(a, 2i4)", "after test1 x = ", x
  print "(a, i4)", "no. final calls = ", ctr
  call test2 (x)
  print "(a, 2i4)", "after test2 x = ", x
  print "(a, i4)", "no. final calls = ",ctr
end

[Bug fortran/114141] ASSOCIATE and complex part ref when associate target is a function

2024-03-15 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=114141

Paul Thomas  changed:

   What|Removed |Added

 Resolution|--- |FIXED
 Status|NEW |RESOLVED

--- Comment #16 from Paul Thomas  ---
This mega-patch, on the scale of the importance of the problem, was required
because of gfortran's one pass parsing. It might be a temporary fix because I
am contemplating how an initial pass of contained procedures might be
introduced.

Fixed on mainline.

Paul

[Bug fortran/87477] [meta-bug] [F03] issues concerning the ASSOCIATE statement

2024-03-15 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87477
Bug 87477 depends on bug 114280, which changed state.

Bug 114280 Summary: ASSOCIATE fails with inquiry references when selector 
function not yet parsed.
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=114280

   What|Removed |Added

 Status|UNCONFIRMED |RESOLVED
 Resolution|--- |FIXED

[Bug fortran/114280] ASSOCIATE fails with inquiry references when selector function not yet parsed.

2024-03-15 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=114280

Paul Thomas  changed:

   What|Removed |Added

 Status|UNCONFIRMED |RESOLVED
 Resolution|--- |FIXED

--- Comment #2 from Paul Thomas  ---
This mega-patch, on the scale of the importance of the problem, was required
because of gfortran's one pass parsing. It might be a temporary fix because I
am contemplating how an initial pass of contained procedures might be
introduced.

Fixed on mainline.

Paul

[Bug fortran/99065] ASSOCIATE function selector expression "no IMPLICIT type" failure

2024-03-15 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=99065

--- Comment #4 from Paul Thomas  ---
This mega-patch, on the scale of the importance of the problem, was required
because of gfortran's one pass parsing. It might be a temporary fix because I
am contemplating how an initial pass of contained procedures might be
introduced.

Fixed on mainline.

Paul

[Bug fortran/87477] [meta-bug] [F03] issues concerning the ASSOCIATE statement

2024-03-15 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87477
Bug 87477 depends on bug 89645, which changed state.

Bug 89645 Summary: No IMPLICIT type error with: ASSOCIATE( X => function() )
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89645

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution|--- |FIXED

[Bug fortran/89645] No IMPLICIT type error with: ASSOCIATE( X => function() )

2024-03-15 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89645

Paul Thomas  changed:

   What|Removed |Added

 Resolution|--- |FIXED
 Status|NEW |RESOLVED

--- Comment #7 from Paul Thomas  ---
This mega-patch, on the scale of the importance of the problem, was required
because of gfortran's one pass parsing. It might be a temporary fix because I
am contemplating how an initial pass of contained procedures might be
introduced.

Fixed on mainline.

Paul

[Bug fortran/114280] New: ASSOCIATE fails with inquiry references when selector function not yet parsed.

2024-03-08 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=114280

Bug ID: 114280
   Summary: ASSOCIATE fails with inquiry references when selector
function not yet parsed.
   Product: gcc
   Version: 13.2.1
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: pault at gcc dot gnu.org
  Target Milestone: ---

Fails identically back to 6.4.1 at least:

  implicit none
  type t
 real :: re
  end type t
  call foo
contains
  subroutine foo ()
associate (x => bar1())
  print *, x%im  ! Has no IMPLICIT type
end associate

associate (x => bar1())
  print *, x%re  ! Invalid character in name
end associate

associate (x => bar2())
  print *, x%re  ! Invalid character in name
end associate

associate (x => bar3())
  print *, x%len  ! Has no IMPLICIT type
end associate
  end
  complex function bar1 ()
bar1 = cmplx(-42., 1.)
  end
  type(t) function bar2 ()
bar2% re = 42.
  end
  character(8) function bar3 ()
bar3 = "Nice one!"
  end
end

Works if:
(i) subroutine foo is placed after functions bar[1-3]; or
(ii) if intrinsics real, imag and len are used instead of inquiry references
and component 're' is renamed.

This bug appears for the same reason as PR99065.

Paul


Paul

[Bug fortran/112834] Class array function selector causes chain of syntax and other spurious errors

2024-03-06 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112834

Paul Thomas  changed:

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution|--- |FIXED

--- Comment #4 from Paul Thomas  ---
Fixed on mainline.

Paul

[Bug fortran/87477] [meta-bug] [F03] issues concerning the ASSOCIATE statement

2024-03-06 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87477
Bug 87477 depends on bug 112834, which changed state.

Bug 112834 Summary: Class array function selector causes chain of syntax and 
other spurious errors
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112834

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution|--- |FIXED

[Bug fortran/114141] ASSOCIATE and complex part ref when associate target is a function

2024-03-02 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=114141

--- Comment #14 from Paul Thomas  ---
To fix the parentheses wrinkle, this works:
diff --git a/gcc/fortran/match.cc b/gcc/fortran/match.cc
index eee569dac91..64f61c50c66 100644
--- a/gcc/fortran/match.cc
+++ b/gcc/fortran/match.cc
@@ -1963,6 +1963,20 @@ gfc_match_associate (void)
  goto assocListError;
}

+  /* If the selector expression is enclosed in parentheses and the
+expression is not a variable, throw the parentheses away.  */
+  while (newAssoc->target->expr_type == EXPR_OP
+&& newAssoc->target->value.op.op == INTRINSIC_PARENTHESES)
+   {
+ if (newAssoc->target->value.op.op1->expr_type == EXPR_VARIABLE)
+   break;
+ else
+   {
+ gfc_expr *e = gfc_copy_expr (newAssoc->target->value.op.op1);
+ gfc_replace_expr (newAssoc->target, e);
+   }
+   }
+
   /* The `variable' field is left blank for now; because the target is not

To maintain compatibility with
https://gcc.gnu.org/pipermail/fortran/2024-January/060092.html:

@@ -2220,7 +2235,8 @@ gfc_match_varspec (gfc_expr *primary, int equiv_flag,
bool sub_flag,
|| tgt_expr->symtree->n.sym->attr.if_source
== IFSRC_DECL);
   permissible = permissible
-   || (tgt_expr && tgt_expr->expr_type == EXPR_OP);
+   || (tgt_expr && (tgt_expr->expr_type == EXPR_OP
+   || (inquiry && tgt_expr->expr_type == EXPR_FUNCTION)));

   if (permissible)
{

[Bug fortran/114141] ASSOCIATE and complex part ref when associate target is a function

2024-03-01 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=114141

--- Comment #13 from Paul Thomas  ---
(In reply to Steve Kargl from comment #11)
...snip...
> I know you had some ASSOCIATE patches in the works, and
> certainly do not want to interfere.  Do you want to
> incorporate my patch or some variation into your work?
> I'm hoping to take a stab at the issue Jerry raised 
> with parentheses this weekend.

Hi Steve,

Interference was not what I had in mind :-)

I was thinking of breaking the patch
https://gcc.gnu.org/pipermail/fortran/2024-January/060092.html in two; the
first to deal with derived type functions and the second for class functions.
Your patch for this PR would sit nicely in the first.

Cheers

Paul

[Bug fortran/114141] ASSOCIATE and complex part ref when associate target is a function

2024-03-01 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=114141

--- Comment #12 from Paul Thomas  ---
(In reply to Steve Kargl from comment #11)
...snip...
> I know you had some ASSOCIATE patches in the works, and
> certainly do not want to interfere.  Do you want to
> incorporate my patch or some variation into your work?
> I'm hoping to take a stab at the issue Jerry raised 
> with parentheses this weekend.

Hi Steve,

Interference was not what I had in mind :-)

I was thinking of breaking the patch
https://gcc.gnu.org/pipermail/fortran/2024-January/060092.html in two; the
first to deal with derived type functions and the second for class functions.
Your patch for this PR would sit nicely in the first.

Cheers

Paul

[Bug fortran/114141] ASSOCIATE and complex part ref when associate target is a function

2024-02-29 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=114141

Paul Thomas  changed:

   What|Removed |Added

 Ever confirmed|0   |1
 Status|UNCONFIRMED |NEW
 CC||pault at gcc dot gnu.org
   Last reconfirmed||2024-02-29

--- Comment #10 from Paul Thomas  ---
(In reply to Jerry DeLisle from comment #9)
> --- snip ---
> > % gfcx -o z a.f90
> > a.f90:5:6:
> > 
> > 5 |   x%im = 42
> >   |  1
> > Error: 'x' at (1) associated to expression cannot be used in
> > a variable definition context (assignment)
> > 
> > Mikael, thanks for the feedback.  I'll see if I can fix
> > the parentheses case this weekend.
> 
> This is definitely a 42 case, which is why I had three '?' in my reply.
> 
> And if you understand this, you are OK in my book. :)

BTW Both nagfor and ifort compile the testcase without complaint.

Your fix is closely related to my patch for not-yet-parsed function selectors.

Cheers

Paul

[Bug fortran/113363] ICE on ASSOCIATE and unlimited polymorphic function

2024-01-17 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=113363

--- Comment #3 from Paul Thomas  ---
(In reply to Paul Thomas from comment #2)
> > 
> > Both allocation with source and assignment are broken :-(
> 
> With numerical output from foo ([1,2,3,4,5]), we get:
> 
>1   3   5  33   1
>1   2   3   4   5
>1   2   3   4   5
> 
> So allocation with source is broken here as well but assignment is OK.

I have confirmed that the construction of e3rhs starting at trans-stmt.cc:6653
is the cause of the problem with allocation. I have to put this on one side
until the end of February.

Paul

[Bug fortran/113363] ICE on ASSOCIATE and unlimited polymorphic function

2024-01-14 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=113363

Paul Thomas  changed:

   What|Removed |Added

   Last reconfirmed||2024-01-14
 Ever confirmed|0   |1
 Status|UNCONFIRMED |NEW
   Assignee|unassigned at gcc dot gnu.org  |pault at gcc dot gnu.org

--- Comment #2 from Paul Thomas  ---

> 
> Both allocation with source and assignment are broken :-(

With numerical output from foo ([1,2,3,4,5]), we get:

   1   3   5  33   1
   1   2   3   4   5
   1   2   3   4   5

So allocation with source is broken here as well but assignment is OK.

[Bug fortran/113363] ICE on ASSOCIATE and unlimited polymorphic function

2024-01-14 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=113363

--- Comment #1 from Paul Thomas  ---
(In reply to anlauf from comment #0)
> While discussing a patch for PR89645/99065, the following issue with
> ASSOCIATE and unlimited polymorphic functions was found:
> 
> https://gcc.gnu.org/pipermail/fortran/2024-January/060098.html
> 
> program p
>   implicit none
>   class(*), allocatable :: x(:)
>   x = foo()
>   call prt (x)
>   deallocate (x)! up to here all is fine...
>   associate (var => foo())  ! <- crash here
> call prt (var)  ! <- or here
>   end associate
> contains
>   function foo() result(res)
> class(*), allocatable :: res(:)
> res = [42]
>   end function foo
>   subroutine prt (x)
> class(*), intent(in) :: x(:)
> select type (x)
> type is (integer)
>print *, x
> class default
>stop 99
> end select
>   end subroutine prt
> end
> 
> 
> This ICEs on current trunk for any of the indicated statements.

The associate bit is fixed with a one liner; with the patch applied:
@@ -2295,7 +2305,8 @@ trans_associate_var (gfc_symbol *sym, gfc_wrapped_block
*block)
 }

   /* Set the stringlength, when needed.  */
-  if (need_len_assign)
+  if (need_len_assign
+  && !(e->symtree->n.sym->attr.function && UNLIMITED_POLY
(e->symtree->n.sym)))
 {
   gfc_se se;
   gfc_init_se (, NULL);

the following gives the output in the comments:
program p
  implicit none
  class(*), allocatable :: x(:)
  allocate(x, source = foo())
  call prt (x)  ! Wrong output "6 hello e"
  deallocate (x)
  x = foo()
  call prt (x)  ! Wrong output "0  "
  deallocate (x)!
  associate (var => foo())  ! Now OK
call prt (var)  ! Now OK - outputs: "6 hello bye   "
  end associate
contains
  function foo() result(res)
class(*), allocatable :: res(:)
res = ["hello ","bye   "]
  end function foo
  subroutine prt (x)
class(*), intent(in) :: x(:)
select type (x)
type is (character(*))
   print *, len(x), x
class default
   stop 99
end select
  end subroutine prt
end

Both allocation with source and assignment are broken :-(

[Bug fortran/89645] No IMPLICIT type error with: ASSOCIATE( X => function() )

2023-12-16 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89645

--- Comment #5 from Paul Thomas  ---
Created attachment 56892
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=56892=edit
An experimental patch for two pass compilation of contained procedures with
failures

I am giving up on this. Failures as follows:

FAIL: gfortran.dg/binding_label_tests_13_main.f03   -O   (test for errors, line
5)
FAIL: gfortran.dg/binding_label_tests_13_main.f03   -O   (test for errors, line
10)
Compiles without errors

FAIL: gfortran.dg/deferred_character_8.f90   -O0  (internal compiler error:
Segmentation fault)
FAIL: gfortran.dg/deferred_character_8.f90   -O0  (test for excess errors)
Compiles and runs OK outside dejagnu

...repeats...
FAIL: gfortran.dg/entry_16.f90   -O0  (internal compiler error: Segmentation
fault)
FAIL: gfortran.dg/entry_16.f90   -O0  (test for excess errors)
...repeats...
FAIL: gfortran.dg/entry_1.f90   -O1  (test for excess errors)
FAIL: gfortran.dg/entry_1.f90   -O2  (test for excess errors)
...repeats...
FAIL: gfortran.dg/entry_13.f90   -O0  (internal compiler error: Segmentation
fault)
FAIL: gfortran.dg/entry_13.f90   -O0  (test for excess errors)
...repeats...
All three entry failures are due to:
internal compiler error: Segmentation fault
0x10941df crash_signal
../../gcc/gcc/toplev.cc:316
0x10cf582 main_block_label
../../gcc/gcc/tree-cfg.cc:1533
0x10cf582 cleanup_dead_labels()
../../gcc/gcc/tree-cfg.cc:1718
0x10dd8d1 build_gimple_cfg
../../gcc/gcc/tree-cfg.cc:241
0x10dd8d1 execute_build_cfg
../../gcc/gcc/tree-cfg.cc:371

FAIL: gfortran.dg/host_assoc_call_3.f90   -O  (test for excess errors)
Not finding the specific, doubly contained 'putaline'

gfortran.dg/namelist_4.f90   -O   (test for errors, line 34)
FAIL: gfortran.dg/namelist_4.f90   -O  (test for excess errors)
Error: ‘f2’ at (1) is not a variable instead of { dg-error "is not a VALUE" }

FAIL: gfortran.dg/pointer_assign_12.f90   -O  (internal compiler error:
gimplification failed)
FAIL: gfortran.dg/pointer_assign_12.f90   -O   (test for errors, line 10)
FAIL: gfortran.dg/pointer_assign_12.f90   -O  (test for excess errors)

   10 |   g => 1 ! { dg-error "Pointer assignment target cannot be a
constant" }
  |
   ^
internal compiler error: gimplification failed
0xd6cd97 gimplify_expr(tree_node**, gimple**, gimple**, bool (*)(tree_node*),
int)
../../gcc/gcc/gimplify.cc:17749

FAIL: gfortran.dg/pr87907.f90   -O  (internal compiler error: Segmentation
fault)
FAIL: gfortran.dg/pr87907.f90   -O   (test for errors, line 15)
FAIL: gfortran.dg/pr87907.f90   -O   (test for errors, line 20)
FAIL: gfortran.dg/pr87907.f90   -O   (test for errors, line 22)
FAIL: gfortran.dg/pr87907.f90   -O  (test for excess errors)
f951: internal compiler error: Segmentation fault
0x10941df crash_signal
../../gcc/gcc/toplev.cc:316
0x97fd53 gfc_match_decl_type_spec(gfc_typespec*, int)
../../gcc/gcc/fortran/decl.cc:4281
0x9816bc gfc_match_data_decl()
../../gcc/gcc/fortran/decl.cc:6286
0x9f7a9f match_word
../../gcc/gcc/fortran/parse.cc:92
0x9f7a9f decode_statement
../../gcc/gcc/fortran/parse.cc:476

FAIL: gfortran.dg/pr95690.f90   -O   (test for errors, line 5)
FAIL: gfortran.dg/pr95690.f90   -O  (test for excess errors)
Error: Function ‘erfc’ requires an argument list at (1)

FAIL: gfortran.dg/pr96102.f90   -O   (test for errors, line 13)
FAIL: gfortran.dg/pr96102.f90   -O   (test for errors, line 14)
FAIL: gfortran.dg/pr96102.f90   -O   (test for errors, line 17)
FAIL: gfortran.dg/pr96102.f90   -O   (test for errors, line 18)
FAIL: gfortran.dg/pr96102.f90   -O  (test for excess errors)
   17 |   if ( n /= 0 ) stop 1! { dg-error "internal procedure of the
same name" }
  |  1
Error: Function ‘n’ requires an argument list at (1)

FAIL: gfortran.dg/pr96102b.f90   -O   (test for errors, line 10)
FAIL: gfortran.dg/pr96102b.f90   -O   (test for errors, line 11)
FAIL: gfortran.dg/pr96102b.f90   -O   (test for errors, line 14)
FAIL: gfortran.dg/pr96102b.f90   -O   (test for errors, line 15)
FAIL: gfortran.dg/pr96102b.f90   -O  (test for excess errors)
Error: Unexpected use of subroutine name ‘n’ at (1)

FAIL: gfortran.dg/proc_ptr_result_2.f90   -O  (test for excess errors)
   35 | call set_fun(aux)
  | 1
Error: Type mismatch in argument ‘y’ at (1); passed REAL(4) to UNKNOWN

XPASS: gfortran.dg/goacc/coarray.f95   -O  TODO (test for errors, line 27)
XPASS: gfortran.dg/goacc/cray-2.f95   -O  TODO (test for errors, line 49)
FAIL: gfortran.dg/goacc/cray-2.f95   -O  (test for excess errors)
XPASS: gfortran.dg/goacc/cray.f95   -O  TODO (test for errors, line 48)
FAIL: gfortran.dg/goacc/cray.f95   -O  (test for excess errors)
FAIL: gfortran.dg/goacc/declare-1.f95   -O   (test for errors, line 13)
FAIL: gfortran.dg/goacc/declare-1.f95   -O  (test for excess errors)
FAIL: 

[Bug fortran/112834] Class array function selector causes chain of syntax and other spurious errors

2023-12-06 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112834

Paul Thomas  changed:

   What|Removed |Added

 Blocks||87477

--- Comment #2 from Paul Thomas  ---
Flagging as a blocker to PR87477.


Referenced Bugs:

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87477
[Bug 87477] [meta-bug] [F03] issues concerning the ASSOCIATE statement

[Bug fortran/112834] Class array function selector causes chain of syntax and other spurious errors

2023-12-06 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112834

Paul Thomas  changed:

   What|Removed |Added

 Status|UNCONFIRMED |NEW
   Assignee|unassigned at gcc dot gnu.org  |pault at gcc dot gnu.org
   Last reconfirmed||2023-12-06
 CC||pault at gcc dot gnu.org
 Ever confirmed|0   |1

--- Comment #1 from Paul Thomas  ---
Created attachment 56814
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=56814=edit
Fix for this PR

I will be submitting this to the list this evening.

Paul

[Bug fortran/112834] New: Class array function selector causes chain of syntax and other spurious errors

2023-12-03 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112834

Bug ID: 112834
   Summary: Class array function selector causes chain of syntax
and other spurious errors
   Product: gcc
   Version: 14.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: pault at gcc dot gnu.org
  Target Milestone: ---

Created attachment 56777
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=56777=edit
testcase demonstrating problem

The attached produces:

[pault@pc30 pr87477]$ rm ./a.out;~/grun/bin/gfortran test.f90
-fdump-tree-original -g;./a.out
test.f90:24:15:

   24 |   if (var1(2)%i .ne. test_array(2)%i) stop 9
  |   1
Error: Syntax error in IF-expression at (1)
test.f90:31:16:

   31 |   if (x(1)%i .ne. test_array(1)%i) stop 11
  |1
Error: Syntax error in IF-expression at (1)
test.f90:39:52:

   39 | print *, "yes, size of 'y' is ", size(y), y(1)
  |1
Error: Syntax error in PRINT statement at (1)
test.f90:44:26:

   44 | end module class_selectors
  |  1
Error: Pointer assignment target in initialization expression does not have the
TARGET attribute at (1)
test.f90:46:7:

   46 |   use class_selectors
  |   1
Fatal Error: Cannot open module file ‘class_selectors.mod’ for reading at (1):
No such file or directory
compilation terminated

Paul

[Bug fortran/89645] No IMPLICIT type error with: ASSOCIATE( X => function() )

2023-12-03 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89645

Paul Thomas  changed:

   What|Removed |Added

   Assignee|unassigned at gcc dot gnu.org  |pault at gcc dot gnu.org

--- Comment #4 from Paul Thomas  ---
Created attachment 56775
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=56775=edit
Deadend fix for this PR

I got as far as I could with this fix up method. The testcase below fails and
so I am going to set aside this approach and tackle what I should have done in
the first place: two step parsing of contained procedures.

The patch contains a fix for class array function selectors that do not work,
even if the selector function is parsed first. I will make a new PR for this
and will break out the patch for it and post it to the list.

Paul

module m
  implicit none
  type t
integer :: i = 0
  end type t
  integer :: i = 0
  type(t), parameter :: test_array (2) = [t(42),t(84)], &
test_scalar = t(99)
end module m
module class_selectors
  use m
  implicit none
  private
  public foo2
contains

  subroutine foo2()
associate (var1 => bar3())
  if (any (var1%i .ne. test_array%i)) stop 8
  if (var1(2)%i .ne. test_array(2)%i) stop 9
!  associate (var3 => var1%i)  ! This still fails
! print *, "yipee"
!  end associate
  select type (x => var1)
type is (t)
  if (any (x%i .ne. test_array%i)) stop 10
  if (x(1)%i .ne. test_array(1)%i) stop 11
class default
  stop 12
  end select
end associate

select type (y => bar3 ())
  type is (t)
print *, "yes, size of 'y' is ", size(y), y(1)
  class default
print *, "no"
end select
  end subroutine foo2

! Since these functions are parsed after 'foo', the symbols were not available
! for the selectors and the fixup, tested here, was necessary.

  function bar3() result(res)
class(t), allocatable :: res(:)
allocate (res, source = test_array)
  end
end module class_selectors

  use class_selectors
  call foo2
end

[Bug fortran/85836] [meta-bug] Fortran 2018 support

2023-12-03 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=85836

--- Comment #7 from Paul Thomas  ---
Created attachment 56774
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=56774=edit
Features 6.x

[Bug fortran/85836] [meta-bug] Fortran 2018 support

2023-12-03 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=85836

--- Comment #6 from Paul Thomas  ---
Created attachment 56773
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=56773=edit
Feature 5.12

  1   2   3   4   5   6   7   8   9   10   >