GCC has been accepted as GSoC 2024 mentoring organization

2024-02-22 Thread Martin Jambor
Hello everyone,

I am pleased that I can announce that we have been accepted to be a GSoC
mentoring organization also in 2024!.

This also means that students are now really starting to look at our
idea page and so if anyone wants to add a project, it is still possible
but we should not delay it much longer.

Thanks to everyone who helped me with this so far. I am very happy that
we'll get this chance to attract new contributors this year too.

Martin



On Mon, Jan 15 2024, Martin Jambor wrote:
> Hello,
>
> another year has passed, Google has announced there will be again Google
> Summer of Code (GsoC) in 2024 and the deadline for organizations to
> apply is already approaching (February 6th).  I'd like to volunteer to
> be the main org-admin for GCC again but let me know if you think I
> shouldn't or that someone else should or if you want to do it instead.
> Otherwise I'll assume that I will and I hope that I can continue to rely
> on David Edelsohn and Thomas Schwinge to back me up and help me with
> some decision making along the way as my co-org-admins.
>
>  The most important bit: 
>
> I would like to ask all (moderately) seasoned GCC contributors to
> consider mentoring a contributor this year and ideally also come up with
> a project that they would like to lead.  I'm collecting proposal on our
> wiki page https://gcc.gnu.org/wiki/SummerOfCode - feel free to add yours
> to the top list there.  Or, if you are unsure, post your offer and
> project idea as a reply here to the mailing list.
>
> Additionally, if you have added an idea to the list in the recent years,
> please review it whether it is still up-to-date or needs adjusting or
> should be removed altogether.
>
> =
>
> At this point, we need to collect list of project ideas.  Eventually,
> each listed project idea should have:
>
>   a) a project title,
>   b) more detailed description of the project (2-5 sentences),
>   c) expected outcomes (we do have a catch-almost-all formulation that
>  outcome is generally patches at the bottom of the list on the
>  wiki),
>   d) skills required/preferred,
>   e) project size - whether it is expected to take approximately 350,
>  175 or just 90 hours (the last option in new in 2024, see below),
>   f) difficulty (easy, hard or medium, but we don't really have easy
>  projects), and
>   g) expected mentors.
>
> Project ideas that come without an offer to also mentor them are always
> fun to discuss, by all means feel free to reply to this email with yours
> and I will attempt to find a mentor, but please be aware that we can
> only use the suggestion it if we actually find one or ideally two.
>
> Everybody in the GCC community is invited to go over
> https://gcc.gnu.org/wiki/SummerOfCode and remove any outdated or
> otherwise bad project suggestions and help improve viable ones.
>
> Finally, please continue helping (prospective) students figure stuff out
> about GCC like you have always done in the past.
>
> As far as I know, GSoC 2024 should be quite similar to the last year,
> the most important parameters probably are these:
>
>   - Contributors (formerly students) must either be full-time students
> or be "beginners to open source."
>
>   - There are now three project sizes: roughly 90 hors (small), roughly
> 175 hours (medium-sized) and roughly 350 hours (large) of work in
> total.  The small option is new this year but because our projects
> usually have a lengthy learning period, I think we will usually want
> to stick to the medium and large variants.
>
>   - Timing should be pretty much as flexible as last year.  The
> recommended "standard" duration is 12 weeks but depending on
> contributor's and mentor's needs and circumstances, projects can
> take anywhere between 10 and 22 weeks.  There will be one mid-term
> and one final evaluation.
>
> For further details you can see:
>
>   - The announcement of GSoC 2024:
> 
> https://opensource.googleblog.com/2023/11/google-summer-of-code-2024-celebrating-20th-year.html
>
>   - GSoC rules:
> https://summerofcode.withgoogle.com/rules
>
>   - The detailed GSoC 2024 timeline:
> https://developers.google.com/open-source/gsoc/timeline
>
>   - Elaborate project idea guidelines:
> https://google.github.io/gsocguides/mentor/defining-a-project-ideas-list
>
> Thank you very much for your participation and help.  Let's hope we
> attract some great contributors again this year.
>
> Martin


[patch, libgfortran] PR105456 Child I/O does not propage iostat

2024-02-22 Thread Jerry D

Hi all,

The attached fix adds a check for an error condition from a UDDTIO 
procedure in the case where there is no actual underlying error, but the 
user defines an error by setting the iostat variable manually before 
returning to the parent READ.


I did not address the case of a formatted WRITE or unformatted 
READ/WRITE until I get some feedback on the approach. If this approach 
is OK I would like to commit and then do a separate patch for the cases 
I just mentioned.


Feedback appreciated.  Regression tested on x86_64. OK for trunk?

Jerry

Author: Jerry DeLisle 
Date:   Thu Feb 22 10:48:39 2024 -0800

libgfortran: Propagate user defined iostat and iomsg.

PR libfortran/105456

libgfortran/ChangeLog:

* io/list_read.c (list_formatted_read_scalar): Add checks
for the case where a user defines their own error codes
and error messages and generate the runtime error.

gcc/testsuite/ChangeLog:

* gfortran.dg/pr105456.f90: New test.diff --git a/gcc/testsuite/gfortran.dg/pr105456.f90 b/gcc/testsuite/gfortran.dg/pr105456.f90
new file mode 100644
index 000..411873f4aed
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/pr105456.f90
@@ -0,0 +1,41 @@
+! { dg-do run }
+! { dg-shouldfail "The users message" }
+module sk1
+  implicit none
+  type char
+ character :: ch
+  end type char
+  interface read (formatted)
+ module procedure read_formatted
+  end interface read (formatted)
+contains
+  subroutine read_formatted (dtv, unit, iotype, vlist, piostat, piomsg)
+class (char), intent(inout) :: dtv
+integer, intent(in) :: unit
+character (len=*), intent(in) :: iotype
+integer, intent(in) :: vlist(:)
+integer, intent(out) :: piostat
+character (len=*), intent(inout) :: piomsg
+character :: ch
+read (unit,fmt='(A1)', advance="no", iostat=piostat, iomsg=piomsg) ch
+piostat = 42
+piomsg="The users message"
+dtv%ch = ch
+  end subroutine read_formatted
+end module sk1
+
+program skip1
+  use sk1
+  implicit none
+  integer :: myerror = 0
+  character(64) :: mymessage = ""
+  type (char) :: x
+  open (10,status="scratch")
+  write (10,'(A)') '', 'a'
+  rewind (10)
+  read (10,*) x
+  print *, myerror, mymessage
+  write (*,'(10(A))') "Read: '",x%ch,"'"
+end program skip1
+! { dg-output ".*(unit = 10, file = .*)" }
+! { dg-output "Fortran runtime error: The users message" }
diff --git a/libgfortran/io/list_read.c b/libgfortran/io/list_read.c
index 3d29cb64813..ee3ab713519 100644
--- a/libgfortran/io/list_read.c
+++ b/libgfortran/io/list_read.c
@@ -2138,6 +2138,7 @@ static int
 list_formatted_read_scalar (st_parameter_dt *dtp, bt type, void *p,
 			int kind, size_t size)
 {
+  char message[MSGLEN];
   gfc_char4_t *q, *r;
   size_t m;
   int c;
@@ -2247,7 +2248,7 @@ list_formatted_read_scalar (st_parameter_dt *dtp, bt type, void *p,
 	  child_iostat = ((dtp->common.flags & IOPARM_HAS_IOSTAT)
 			  ? dtp->common.iostat : &noiostat);
 
-	  /* Set iomsge, intent(inout).  */
+	  /* Set iomsg, intent(inout).  */
 	  if (dtp->common.flags & IOPARM_HAS_IOMSG)
 	{
 	  child_iomsg = dtp->common.iomsg;
@@ -2266,6 +2267,25 @@ list_formatted_read_scalar (st_parameter_dt *dtp, bt type, void *p,
 			  iotype_len, child_iomsg_len);
 	  dtp->u.p.child_saved_iostat = *child_iostat;
 	  dtp->u.p.current_unit->child_dtio--;
+
+
+	  if ((dtp->u.p.child_saved_iostat != 0) &&
+	  !(dtp->common.flags & IOPARM_HAS_IOMSG) &&
+	  !(dtp->common.flags & IOPARM_HAS_IOSTAT))
+	{
+	  /* Trim trailing spaces from the message.  */
+	  for(int i = IOMSG_LEN - 1; i > 0; i--)
+		if (!isspace(child_iomsg[i]))
+		  {
+		/* Add two to get back to the end of child_iomsg.  */
+		child_iomsg_len = i+2;
+		break;
+		  }
+	  free_line (dtp);
+	  snprintf (message, child_iomsg_len, child_iomsg);
+	  generate_error (&dtp->common, dtp->u.p.child_saved_iostat,
+			  message);
+	}
   }
   break;
 default:


Re: [PATCH] Fix fortran/PR114024

2024-02-22 Thread Harald Anlauf

Hi Steve!

On 2/22/24 01:52, Steve Kargl wrote:

On Wed, Feb 21, 2024 at 01:42:32PM -0800, Steve Kargl wrote:

On Wed, Feb 21, 2024 at 10:20:43PM +0100, Harald Anlauf wrote:

On 2/21/24 22:00, Steve Kargl wrote:

memleak vs ICE.  I think I'll take one over the other.
Probably need to free code->expr3 before the copy.


Yep.


I tried gfc_replace_expr in an earlier patch.  It did not
work.



I tried freeing code->expr3 before assigning the new expression.
That leads to

% gfcx -c ~/gcc/gccx/gcc/testsuite/gfortran.dg/allocate_with_source_28.f90
pid 69473 comm f951 has trashed its stack, killing
gfortran: internal compiler error: Illegal instruction signal terminated 
program f951


Right.  I also don't see what the lifetimes of the expressions are.

But is the gfc_copy_expr really needed?  Wouldn't the following suffice?

  code->expr3 = gfc_get_parentheses (code->expr3);


If I don't free code->expr3 but simply assign the new
expression from gfc_get_parentheses(), your example
now compiles are executes are expected.  It now
allocate_with_source_28.f90.  Caveat:  I don't know
how to test the CLASS uu.


- it still fails on the following code, because the traversal
of the refs is incomplete / wrong:

program foo
 implicit none
 complex   :: cmp(3)
 real, pointer :: pp(:)
 class(*), allocatable :: uu(:)
 type t
real :: re
real :: im
 end type t
 type u
type(t) :: tt(3)
 end type u
 type(u) :: cc

 cmp = (3.45,6.78)
 cc% tt% re = cmp% re
 cc% tt% im = cmp% im
 allocate (pp, source = cc% tt% im)   ! ICE


cc%tt%im isn't a complex-part-ref, so this seems to
be a different (maybe related) issue.  Does the code
compile with 'source = (cc%tt%im)'?  If so, perhaps,
detecting a component reference and doing the simply
wrapping with parentheses can be done.


Yes, that's why I tried to make up the above example.
I think %re and %im are not too special, they work
here pretty much like component refs elsewhere.



I see.  The %re and %im complex-part-ref correspond to
ref->u.i == INQUIRY_RE and INQUIRY_IM, respectively.
A part-ref for a user-defined type doesn't have an
INQUIRY_xxx, so we'll need to see if there is a way to
easily identify, e.g., cc%tt%re from your testcase.


The attach patch uses ref->type == REF_COMPONENT to deal
with the above code.


I actually wanted to draw your attention away from the
real/complex stuff, because that is not really the point.
When do we actually need to enforce the parentheses?

I tried the following, and it seems to work:

  if (code->expr3->expr_type == EXPR_VARIABLE
  && is_subref_array (code->expr3))
code->expr3 = gfc_get_parentheses (code->expr3);

(Beware: this is not regtested!)

On the positive side, it not only seems to fix the cases in question,
but also substring references etc., like the following:

program foo
  implicit none
  complex   :: cmp(3) = (3.45,6.78)
  real, pointer :: pp(:)
  integer, allocatable  :: aa(:)
  class(*), allocatable :: uu(:), vv(:)
  type t   ! pseudo "complex" type
 real :: re
 real :: im
  end type t
  type ci  ! "complex integer" type
 integer :: re
 integer :: im
  end type ci
  type u
 type(t)  :: tt(3)
 type(ci) :: ii(3)
  end type u
  type(u) :: cc
  character(3)  :: str(3) = ["abc","def","ghi"]
  character(:), allocatable :: ac(:)

  allocate (ac, source=str(1::2)(2:3))
  print *, str(1::2)(2:3)
  call my_print (ac)
  cc% tt% re = cmp% re
  cc% tt% im = cmp% im
  cc% ii% re = nint (cmp% re)
  cc% ii% im = nint (cmp% im)
  print *, "re=", cc% tt% re
  print *, "im=", cc% tt% im
  allocate (pp, source = cc% tt% re)
  print *, pp
  allocate (uu, source = cc% tt% im)
  call my_print (uu)
  allocate (vv, source = cc% ii% im)
  call my_print (vv)
contains
  subroutine my_print (x)
class(*), intent(in) :: x(:)
select type (x)
type is (real)
   print *, "'real':", x
type is (integer)
   print *, "'integer':", x
type is (character(*))
   print *, "'character':", x
end select
  end subroutine my_print
end

Cheers,
Harald




Re: [PATCH] Fix fortran/PR114024

2024-02-22 Thread Steve Kargl
On Thu, Feb 22, 2024 at 09:22:37PM +0100, Harald Anlauf wrote:
> Hi Steve!
> 
> On 2/22/24 01:52, Steve Kargl wrote:
> > On Wed, Feb 21, 2024 at 01:42:32PM -0800, Steve Kargl wrote:
> > > On Wed, Feb 21, 2024 at 10:20:43PM +0100, Harald Anlauf wrote:
> > > > On 2/21/24 22:00, Steve Kargl wrote:
> > > > > memleak vs ICE.  I think I'll take one over the other.
> > > > > Probably need to free code->expr3 before the copy.
> > > > 
> > > > Yep.
> > > > 
> > > > > I tried gfc_replace_expr in an earlier patch.  It did not
> > > > > work.
> > 
> > I tried freeing code->expr3 before assigning the new expression.
> > That leads to
> > 
> > % gfcx -c ~/gcc/gccx/gcc/testsuite/gfortran.dg/allocate_with_source_28.f90
> > pid 69473 comm f951 has trashed its stack, killing
> > gfortran: internal compiler error: Illegal instruction signal terminated 
> > program f951
> 
> Right.  I also don't see what the lifetimes of the expressions are.
> 
> But is the gfc_copy_expr really needed?  Wouldn't the following suffice?
> 
>   code->expr3 = gfc_get_parentheses (code->expr3);

It's been awhile since I use gfc_copy_expr, gfc_replace_expr, etc.
I did not try the above.  If that works, then we should use that
for simplicity.

> > If I don't free code->expr3 but simply assign the new
> > expression from gfc_get_parentheses(), your example
> > now compiles are executes are expected.  It now
> > allocate_with_source_28.f90.  Caveat:  I don't know
> > how to test the CLASS uu.
> > 
> > > > > > - it still fails on the following code, because the traversal
> > > > > > of the refs is incomplete / wrong:
> > > > > > 
> > > > > > program foo
> > > > > >  implicit none
> > > > > >  complex   :: cmp(3)
> > > > > >  real, pointer :: pp(:)
> > > > > >  class(*), allocatable :: uu(:)
> > > > > >  type t
> > > > > > real :: re
> > > > > > real :: im
> > > > > >  end type t
> > > > > >  type u
> > > > > > type(t) :: tt(3)
> > > > > >  end type u
> > > > > >  type(u) :: cc
> > > > > > 
> > > > > >  cmp = (3.45,6.78)
> > > > > >  cc% tt% re = cmp% re
> > > > > >  cc% tt% im = cmp% im
> > > > > >  allocate (pp, source = cc% tt% im)   ! ICE
> > > > > 
> > > > > cc%tt%im isn't a complex-part-ref, so this seems to
> > > > > be a different (maybe related) issue.  Does the code
> > > > > compile with 'source = (cc%tt%im)'?  If so, perhaps,
> > > > > detecting a component reference and doing the simply
> > > > > wrapping with parentheses can be done.
> > > > 
> > > > Yes, that's why I tried to make up the above example.
> > > > I think %re and %im are not too special, they work
> > > > here pretty much like component refs elsewhere.
> > > > 
> > > 
> > > I see.  The %re and %im complex-part-ref correspond to
> > > ref->u.i == INQUIRY_RE and INQUIRY_IM, respectively.
> > > A part-ref for a user-defined type doesn't have an
> > > INQUIRY_xxx, so we'll need to see if there is a way to
> > > easily identify, e.g., cc%tt%re from your testcase.
> > 
> > The attach patch uses ref->type == REF_COMPONENT to deal
> > with the above code.
> 
> I actually wanted to draw your attention away from the
> real/complex stuff, because that is not really the point.
> When do we actually need to enforce the parentheses?

This is essentially my concern.  I was inserting parentheses
only if I determined they were needed (to avoid unnecessary
temporary variable).  The code paththat enters the else portion
of the following if-else-stmt, where a temporary is created.
That is, 

allocate(x, source=z%re) becomes allocate(x, source=(z%re))
and from code generation viewpoint this is

tmp = (z%re)
allocate(x, sourcer=tmp)
deallocate(tmp)

> I tried the following, and it seems to work:
> 
>   if (code->expr3->expr_type == EXPR_VARIABLE
> && is_subref_array (code->expr3))
>   code->expr3 = gfc_get_parentheses (code->expr3);
> 
> (Beware: this is not regtested!)
> 
> On the positive side, it not only seems to fix the cases in question,
> but also substring references etc., like the following:

If the above passes a regression test, then by all means we should
use it.  I did not consider the substring case.  Even if unneeded
parentheses are inserted, which may cause generation of a temporary
variable, I hope users are not using 'allocate(x,source=z%re)' is
some deeply nested crazy loops structure.

BTW, my patch and I suspect your improved patch also
fixes 'allocate(x,mold=z%re)'.  Consider,

   complex z(3)
   real, allocatable :: x(:)
   z = 42
   allocate(x, mold=z%re)
   print *, size(x)
   end

% gfortran13 -o z a.f90
a.f90:9:25:

9 |allocate(x, mold=z%re)
  | 1
internal compiler error: in retrieve_last_ref, at fortran/trans-array.cc:6070
0x247d7a679 __libc_start1
/usr/src/lib/libc/csu/libc_start1.c:157

% gfcx -o z a.f90 && ./z
   3



-- 
Steve


Re: [PATCH] Fix fortran/PR114024

2024-02-22 Thread Harald Anlauf

On 2/22/24 22:01, Steve Kargl wrote:

On Thu, Feb 22, 2024 at 09:22:37PM +0100, Harald Anlauf wrote:

On the positive side, it not only seems to fix the cases in question,
but also substring references etc., like the following:


If the above passes a regression test, then by all means we should
use it.  I did not consider the substring case.  Even if unneeded
parentheses are inserted, which may cause generation of a temporary
variable, I hope users are not using 'allocate(x,source=z%re)' is
some deeply nested crazy loops structure.


First thing is code correctness.  There are cases where the
allocation shall preserve the array bounds, which is where
we must avoid the parentheses at all cost.  But these cases
should be very limited.  (There are some code comments/TODOs
regarding this and an open PR by Tobias(?)).

The cases we are currently discussing are even requiring(!)
the resetting of the lower bounds to 1, so your suggestion
to enforce parentheses does not look unreasonable.

BTW: If someone uses allocate in a tight loop, he/she deserves
to be punished anyway...


BTW, my patch and I suspect your improved patch also
fixes 'allocate(x,mold=z%re)'.  Consider,

complex z(3)
real, allocatable :: x(:)
z = 42ha
allocate(x, mold=z%re)
print *, size(x)
end

% gfortran13 -o z a.f90
a.f90:9:25:

 9 |allocate(x, mold=z%re)
   | 1
internal compiler error: in retrieve_last_ref, at fortran/trans-array.cc:6070
0x247d7a679 __libc_start1
 /usr/src/lib/libc/csu/libc_start1.c:157

% gfcx -o z a.f90 && ./z
3



Nice!  I completely forgot about MOLD...

So the only missing pieces are a really comprehensive testcase
and successful regtests...

Cheers,
Harald