public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/113503] New: [14 Regression] xtb test miscompilation starting with r14-870
@ 2024-01-19 12:49 jakub at gcc dot gnu.org
  2024-01-19 12:49 ` [Bug fortran/113503] " jakub at gcc dot gnu.org
                   ` (8 more replies)
  0 siblings, 9 replies; 10+ messages in thread
From: jakub at gcc dot gnu.org @ 2024-01-19 12:49 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=113503

            Bug ID: 113503
           Summary: [14 Regression] xtb test miscompilation starting with
                    r14-870
           Product: gcc
           Version: 14.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
          Assignee: unassigned at gcc dot gnu.org
          Reporter: jakub at gcc dot gnu.org
  Target Milestone: ---

Since r14-870-g6c95fe9bc0553743098eeaa739f14b885050fa42 4 xtb tests seem to be
miscompiled, they crash due to memcpy into NULL pointer.

Reduced testcase is:
module xtb_solv_input
   implicit none
   private
   public :: TSolvInput
   type :: TSolvInput
      character(len=:), allocatable :: solvent
   end type
end module
module xtb_main_setup
   use xtb_solv_input, only : TSolvInput
   private
   public :: addSolvationModel
contains
subroutine addSolvationModel(input)
   type(TSolvInput), intent(in) :: input
end subroutine
end module
program xtb
    use xtb_solv_input, only : TSolvInput
    use xtb_main_setup, only : addSolvationModel
    integer :: iMol
    character(len=*), parameter :: solvents(10) = [character(len=20) ::&
      & "h2o", "chcl3", "thf", "acetonitrile", "toluene", &
      & "ch2cl2", "ether", "methanol", "cs2", "dmso"]
    do iMol = 1, 10
      call addSolvationModel(TSolvInput(solvent=trim(solvents(iMol))))
    end do
end program

When compiled with -O2 -fno-inline -Wuninitialized starting with that revision
it emits:
xtb.f90:26:70:

   26 |       call addSolvationModel(TSolvInput(solvent=trim(solvents(iMol))))
      |                                                                      ^
Warning: ‘len.8’ is used uninitialized [-Wuninitialized]
xtb.f90:26:70:

   26 |       call addSolvationModel(TSolvInput(solvent=trim(solvents(iMol))))
      |                                                                      ^
note: ‘len.8’ declared here
warning.  This reduced test doesn't crash, but the unreduced one crashes
exactly because of the uninitialized use - when the uninitialized var happens
to contain some huge value (0x7fffffffffffe0b0 or so in my case), that value is
passed to malloc,
malloc obviously returns NULL as I don't have that much memory and the code
then tries to memcpy "h2o" into NULL.

The bug is visible in the gimple dump already:
            integer(kind=8) len.8;
            integer(kind=8) slen.9;

            try
              {
                slen.9 = len.8;
                slen.18_1 = (sizetype) slen.9;
                _2 = MAX_EXPR <slen.18_1, 1>;
                _3 = __builtin_malloc (_2);
                tsolvinput.6.solvent = _3;
                tsolvinput.6._solvent_length = slen.9;
                _4 = (integer(kind=8)) imol;
                _5 = _4 + -1;
                _6 = &solvents[_5];
                _gfortran_string_trim (&len.8, &pstr.7, 20, _6);
                len.19_7 = len.8;
                len.20_8 = (unsigned long) len.19_7;
                pstr.21_9 = pstr.7;
                _10 = tsolvinput.6.solvent;
                __builtin_memcpy (_10, pstr.21_9, len.20_8);
                len.22_11 = len.8;
In r14-868 instead it looked like
            integer(kind=8) len.8;
            integer(kind=8) D.4372;
            character(kind=1) * pstr.9;
            integer(kind=8) len.10;

            try
              {
                _1 = (integer(kind=8)) imol;
                _2 = _1 + -1;
                _3 = &solvents[_2];
                _gfortran_string_trim (&len.8, &pstr.7, 20, _3);
                len.19_4 = len.8;
                if (len.19_4 > 0) goto <D.4416>; else goto <D.4417>;
                <D.4416>:
                pstr.20_5 = pstr.7;
                __builtin_free (pstr.20_5);

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

* [Bug fortran/113503] [14 Regression] xtb test miscompilation starting with r14-870
  2024-01-19 12:49 [Bug fortran/113503] New: [14 Regression] xtb test miscompilation starting with r14-870 jakub at gcc dot gnu.org
@ 2024-01-19 12:49 ` jakub at gcc dot gnu.org
  2024-01-19 16:59 ` anlauf at gcc dot gnu.org
                   ` (7 subsequent siblings)
  8 siblings, 0 replies; 10+ messages in thread
From: jakub at gcc dot gnu.org @ 2024-01-19 12:49 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=113503

Jakub Jelinek <jakub at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |pault at gcc dot gnu.org
   Target Milestone|---                         |14.0
           Priority|P3                          |P1

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

* [Bug fortran/113503] [14 Regression] xtb test miscompilation starting with r14-870
  2024-01-19 12:49 [Bug fortran/113503] New: [14 Regression] xtb test miscompilation starting with r14-870 jakub at gcc dot gnu.org
  2024-01-19 12:49 ` [Bug fortran/113503] " jakub at gcc dot gnu.org
@ 2024-01-19 16:59 ` anlauf at gcc dot gnu.org
  2024-01-19 17:45 ` anlauf at gcc dot gnu.org
                   ` (6 subsequent siblings)
  8 siblings, 0 replies; 10+ messages in thread
From: anlauf at gcc dot gnu.org @ 2024-01-19 16:59 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=113503

--- Comment #1 from anlauf at gcc dot gnu.org ---
When trying to further reduce the code I get either an ICE or an
uninitialized-warning for:

program xtb
  implicit none
  type :: TSolvInput
     character(len=:), allocatable :: solvent
  end type
  character(len=20) :: solvents(1) = 'h2o'

! call addSolvationModel(TSolvInput(solvent=     solvents(1)))  ! ICE
  call addSolvationModel(TSolvInput(solvent=trim(solvents(1)))) ! Warning

contains
  subroutine addSolvationModel(input)
    type(TSolvInput), intent(in) :: input
  end
end

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

* [Bug fortran/113503] [14 Regression] xtb test miscompilation starting with r14-870
  2024-01-19 12:49 [Bug fortran/113503] New: [14 Regression] xtb test miscompilation starting with r14-870 jakub at gcc dot gnu.org
  2024-01-19 12:49 ` [Bug fortran/113503] " jakub at gcc dot gnu.org
  2024-01-19 16:59 ` anlauf at gcc dot gnu.org
@ 2024-01-19 17:45 ` anlauf at gcc dot gnu.org
  2024-01-20  9:00 ` pinskia at gcc dot gnu.org
                   ` (5 subsequent siblings)
  8 siblings, 0 replies; 10+ messages in thread
From: anlauf at gcc dot gnu.org @ 2024-01-19 17:45 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=113503

--- Comment #2 from anlauf at gcc dot gnu.org ---
(In reply to anlauf from comment #1)
> When trying to further reduce the code I get either an ICE or an
> uninitialized-warning for:

program xtb
  implicit none
  type :: TSolvInput
     character(len=:), allocatable :: solvent
  end type
  character(len=20) :: solvents(1) = 'h2o'
  type(TSolvInput)  :: x
! x = TSolvInput(solvent=     solvents(1))  ! ICE
  x = TSolvInput(solvent=trim(solvents(1))) ! Warning
end


So it clearly comes from the constructor.

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

* [Bug fortran/113503] [14 Regression] xtb test miscompilation starting with r14-870
  2024-01-19 12:49 [Bug fortran/113503] New: [14 Regression] xtb test miscompilation starting with r14-870 jakub at gcc dot gnu.org
                   ` (2 preceding siblings ...)
  2024-01-19 17:45 ` anlauf at gcc dot gnu.org
@ 2024-01-20  9:00 ` pinskia at gcc dot gnu.org
  2024-01-31 17:21 ` jakub at gcc dot gnu.org
                   ` (4 subsequent siblings)
  8 siblings, 0 replies; 10+ messages in thread
From: pinskia at gcc dot gnu.org @ 2024-01-20  9:00 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=113503

Andrew Pinski <pinskia at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
     Ever confirmed|0                           |1
   Last reconfirmed|                            |2024-01-20

--- Comment #3 from Andrew Pinski <pinskia at gcc dot gnu.org> ---
.

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

* [Bug fortran/113503] [14 Regression] xtb test miscompilation starting with r14-870
  2024-01-19 12:49 [Bug fortran/113503] New: [14 Regression] xtb test miscompilation starting with r14-870 jakub at gcc dot gnu.org
                   ` (3 preceding siblings ...)
  2024-01-20  9:00 ` pinskia at gcc dot gnu.org
@ 2024-01-31 17:21 ` jakub at gcc dot gnu.org
  2024-02-16 12:47 ` jakub at gcc dot gnu.org
                   ` (3 subsequent siblings)
  8 siblings, 0 replies; 10+ messages in thread
From: jakub at gcc dot gnu.org @ 2024-01-31 17:21 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=113503

--- Comment #4 from Jakub Jelinek <jakub at gcc dot gnu.org> ---
It is the
PR fortran/82774
(alloc_scalar_allocatable_subcomponent): Shorten the function
name and replace the symbol argument with the se string length.
If a deferred length character length is either not present or
is not a variable, give the typespec a variable and assign the
string length to that. Use gfc_deferred_strlen to find the
hidden string length component.
(gfc_trans_subcomponent_assign): Convert the expression before
the call to alloc_scalar_allocatable_subcomponent so that a
good string length is provided.
(gfc_trans_structure_assign): Remove the unneeded derived type
symbol from calls to gfc_trans_subcomponent_assign.
part of the changes that cause this, reverting those hunks (had to revert one
manually as tree size; declaration has been added there later) makes the
testcase
not warn anymore or in the other case not ICE anymore.

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

* [Bug fortran/113503] [14 Regression] xtb test miscompilation starting with r14-870
  2024-01-19 12:49 [Bug fortran/113503] New: [14 Regression] xtb test miscompilation starting with r14-870 jakub at gcc dot gnu.org
                   ` (4 preceding siblings ...)
  2024-01-31 17:21 ` jakub at gcc dot gnu.org
@ 2024-02-16 12:47 ` jakub at gcc dot gnu.org
  2024-02-16 13:24 ` jakub at gcc dot gnu.org
                   ` (2 subsequent siblings)
  8 siblings, 0 replies; 10+ messages in thread
From: jakub at gcc dot gnu.org @ 2024-02-16 12:47 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=113503

--- Comment #5 from Jakub Jelinek <jakub at gcc dot gnu.org> ---
For the warning case, I think
--- gcc/fortran/trans-expr.cc.jj        2024-02-14 14:26:19.764810614 +0100
+++ gcc/fortran/trans-expr.cc   2024-02-16 13:22:48.693104239 +0100
@@ -9253,19 +9253,20 @@ gfc_trans_subcomponent_assign (tree dest
           || (cm->ts.type == BT_CLASS && CLASS_DATA (cm)->attr.allocatable
               && expr->ts.type != BT_CLASS)))
     {
+      tree size;
+
       gfc_init_se (&se, NULL);
       gfc_conv_expr (&se, expr);
-      tree size;

+      /* The remainder of these instructions follow the if (cm->attr.pointer)
+        if (!cm->attr.dimension) part above.  */
+      gfc_add_block_to_block (&block, &se.pre);
       /* Take care about non-array allocatable components here.  The alloc_*
         routine below is motivated by the alloc_scalar_allocatable_for_
         assignment() routine, but with the realloc portions removed and
         different input.  */
       alloc_scalar_allocatable_subcomponent (&block, dest, cm, expr,
                                             se.string_length);
-      /* The remainder of these instructions follow the if (cm->attr.pointer)
-        if (!cm->attr.dimension) part above.  */
-      gfc_add_block_to_block (&block, &se.pre);

       if (expr->symtree && expr->symtree->n.sym->attr.proc_pointer
          && expr->symtree->n.sym->attr.dummy)
should fix this.  I don't see how code in se.pre could depend on what
alloc_scalar_allocatable_subcomponent emits, and clearly from the #c0 testcase
there can be a dependency in the other direction.

As for the ICE case, this is due to
      if (!expr2->ts.u.cl->backend_decl
          || !VAR_P (expr2->ts.u.cl->backend_decl))
        expr2->ts.u.cl->backend_decl = gfc_create_var (TREE_TYPE (slen),
                                                       "slen");
      gfc_add_modify (block, expr2->ts.u.cl->backend_decl, slen);
expr2->ts.u.cl->backend_decl here is INTEGER_CST and slen is the same
INTEGER_CST (20 in both cases), so changing expr2->ts.u.cl->backend_decl to a
temporary variable pushed into current block is definitely undesirable, it
means references to that slen var can be emitted even before or after the
containing block into which the temporary is pushed using pushdecl.

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

* [Bug fortran/113503] [14 Regression] xtb test miscompilation starting with r14-870
  2024-01-19 12:49 [Bug fortran/113503] New: [14 Regression] xtb test miscompilation starting with r14-870 jakub at gcc dot gnu.org
                   ` (5 preceding siblings ...)
  2024-02-16 12:47 ` jakub at gcc dot gnu.org
@ 2024-02-16 13:24 ` jakub at gcc dot gnu.org
  2024-02-17 15:57 ` cvs-commit at gcc dot gnu.org
  2024-02-17 16:14 ` jakub at gcc dot gnu.org
  8 siblings, 0 replies; 10+ messages in thread
From: jakub at gcc dot gnu.org @ 2024-02-16 13:24 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=113503

Jakub Jelinek <jakub at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|NEW                         |ASSIGNED
           Assignee|unassigned at gcc dot gnu.org      |jakub at gcc dot gnu.org

--- Comment #6 from Jakub Jelinek <jakub at gcc dot gnu.org> ---
Created attachment 57436
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=57436&action=edit
gcc14-pr113503.patch

So far only lightly tested patch (make -j32 check-gfortran).

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

* [Bug fortran/113503] [14 Regression] xtb test miscompilation starting with r14-870
  2024-01-19 12:49 [Bug fortran/113503] New: [14 Regression] xtb test miscompilation starting with r14-870 jakub at gcc dot gnu.org
                   ` (6 preceding siblings ...)
  2024-02-16 13:24 ` jakub at gcc dot gnu.org
@ 2024-02-17 15:57 ` cvs-commit at gcc dot gnu.org
  2024-02-17 16:14 ` jakub at gcc dot gnu.org
  8 siblings, 0 replies; 10+ messages in thread
From: cvs-commit at gcc dot gnu.org @ 2024-02-17 15:57 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=113503

--- Comment #7 from GCC Commits <cvs-commit at gcc dot gnu.org> ---
The master branch has been updated by Jakub Jelinek <jakub@gcc.gnu.org>:

https://gcc.gnu.org/g:296284a9dbb7df4485cc5f1d3e975fdb4b8a10b8

commit r14-9049-g296284a9dbb7df4485cc5f1d3e975fdb4b8a10b8
Author: Jakub Jelinek <jakub@redhat.com>
Date:   Sat Feb 17 16:54:08 2024 +0100

    fortran: gfc_trans_subcomponent_assign fixes [PR113503]

    The r14-870 changes broke xtb package tests (reduced testcase is the first
    one below) and caused ICEs on a test derived from that (the second one).
    For the
      x = T(u = trim (us(1)))
    statement, before that change gfortran used to emit weird code with
    2 trim calls:
          _gfortran_string_trim (&len.2, (void * *) &pstr.1, 20, &us[0]);
          if (len.2 > 0)
            {
              __builtin_free ((void *) pstr.1);
            }
          D.4275 = len.2;
          t.0.u = (character(kind=1)[1:0] *) __builtin_malloc (MAX_EXPR
<(sizetype) D.4275, 1>);
          t.0._u_length = D.4275;
          _gfortran_string_trim (&len.4, (void * *) &pstr.3, 20, &us[0]);
          (void) __builtin_memcpy ((void *) t.0.u, (void *) pstr.3, (unsigned
long) NON_LVALUE_EXPR <len.4>);
          if (len.4 > 0)
            {
              __builtin_free ((void *) pstr.3);
            }
    That worked at runtime, though it is wasteful.
    That commit changed it to:
          slen.3 = len.2;
          t.0.u = (character(kind=1)[1:0] *) __builtin_malloc (MAX_EXPR
<(sizetype) slen.3, 1>);
          t.0._u_length = slen.3;
          _gfortran_string_trim (&len.2, (void * *) &pstr.1, 20, &us[0]);
          (void) __builtin_memcpy ((void *) t.0.u, (void *) pstr.1, (unsigned
long) NON_LVALUE_EXPR <len.2>);
          if (len.2 > 0)
            {
              __builtin_free ((void *) pstr.1);
            }
    which results in -Wuninitialized warning later on and if one is unlucky and
    the uninitialized len.2 variable is smaller than the trimmed length, it
    results in heap overflow and often crashes later on.
    The bug above is clear, len.2 is only initialized in the
    _gfortran_string_trim (&len.2, (void * *) &pstr.1, 20, &us[0]);
    call, but used before that.  Now, the
          slen.3 = len.2;
          t.0.u = (character(kind=1)[1:0] *) __builtin_malloc (MAX_EXPR
<(sizetype) slen.3, 1>);
          t.0._u_length = slen.3;
    statements come from the alloc_scalar_allocatable_subcomponent call,
    while
          _gfortran_string_trim (&len.2, (void * *) &pstr.1, 20, &us[0]);
    from the gfc_conv_expr (&se, expr); call which is done before the
    alloc_scalar_allocatable_subcomponent call, but is only appended later on
    with gfc_add_block_to_block (&block, &se.pre);
    Now, obviously the alloc_scalar_allocatable_subcomponent emitted statements
    can depend on the se.pre sequence statements which can compute variables
    used by alloc_scalar_allocatable_subcomponent like the length.
    On the other side, I think the se.pre sequence really shouldn't depend
    on the changes done by alloc_scalar_allocatable_subcomponent, that is
    initializing the FIELD_DECLs of the destination allocatable subcomponent
    only, the gfc_conv_expr statements are already created, so all they could
    in theory depend above is on t.0.u or t.0._u_length, but I believe if the
    rhs dependened on the lhs content (which is allocated by those statements
    but really uninitialized), it would need to be discovered by the dependency
    analysis and forced into a temporary.
    So, in order to fix the first testcase, the second hunk of the patch just
    emits the se.pre block before the alloc_scalar_allocatable_subcomponent
    changes rather than after it.

    The second problem is an ICE on the second testcase.  expr in the caller
    (expr2 inside of alloc_scalar_allocatable_subcomponent) has
    expr2->ts.u.cl->backend_decl already set, INTEGER_CST 20, but
    alloc_scalar_allocatable_subcomponent overwrites it to a new VAR_DECL
    which it assigns a value to before the malloc.  That can work if the only
    places the expr2->ts is ever used are in the same local block or its
    subblocks (and only if it is dominated by the code emitted by
    alloc_scalar_allocatable_subcomponent, so e.g. not if that call is inside
    of a conditional code and use later unconditional), but doesn't work
    if expr2->ts is used before that block or after it.  So, the exact ICE is
    because of:
      slen.1 = 20;
        static character(kind=1) us[1][1:20] = {"foo                 "};
      x.u = 0B;
      x._u_length = 0;
      {
        struct t t.0;
        struct t D.4308;

        {
          integer(kind=8) slen.1;

          slen.1 = 20;
          t.0.u = (character(kind=1)[1:0] *) __builtin_malloc (MAX_EXPR
<(sizetype) slen.1, 1>);
          t.0._u_length = slen.1;
          (void) __builtin_memcpy ((void *) t.0.u, (void *) &us[0], 20);
        }
    where the first slen.1 = 20; is emitted because it sees us has a VAR_DECL
    ts.u.cl->backend_decl and so it wants to initialize it to the actual
length.
    This is invalid GENERIC, because the slen.1 variable is only declared
inside
    of a {} later on and so uses outside of it are wrong.  Similarly wrong
would
    be if it is used later on.  E.g. in the same testcase if it has
      type(T) :: x, y
      x = T(u = us(1))
      y%u = us(1)
    then there is
        {
          integer(kind=8) slen.1;

          slen.1 = 20;
          t.0.u = (character(kind=1)[1:0] *) __builtin_malloc (MAX_EXPR
<(sizetype) slen.1, 1>);
          t.0._u_length = slen.1;
          (void) __builtin_memcpy ((void *) t.0.u, (void *) &us[0], 20);
        }
    ...
        if (y.u != 0B) goto L.1;
        y.u = (character(kind=1)[1:0] *) __builtin_malloc (MAX_EXPR <(sizetype)
slen.1, 1>);
    i.e. another use of slen.1, this time after slen.1 got out of scope.

    I really don't understand why the code modifies
    expr2->ts.u.cl->backend_decl, expr2 isn't used there anywhere except for
    expr2->ts.u.cl->backend_decl expressions, so hacks like save the previous
    value, overwrite it temporarily over some call that will use expr2 and
    restore afterwards aren't needed - there are no such calls, so the
    following patch fixes it just by not messing up with
    expr2->ts.u.cl->backend_decl, only set it to size variable and overwrite
    that with a temporary if needed.

    2024-02-17  Jakub Jelinek  <jakub@redhat.com>

            PR fortran/113503
            * trans-expr.cc (alloc_scalar_allocatable_subcomponent): Don't
            overwrite expr2->ts.u.cl->backend_decl, instead set size to
            expr2->ts.u.cl->backend_decl first and use size instead of
            expr2->ts.u.cl->backend_decl.
            (gfc_trans_subcomponent_assign): Emit se.pre into block
            before calling alloc_scalar_allocatable_subcomponent instead of
            after it.

            * gfortran.dg/pr113503_1.f90: New test.
            * gfortran.dg/pr113503_2.f90: New test.

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

* [Bug fortran/113503] [14 Regression] xtb test miscompilation starting with r14-870
  2024-01-19 12:49 [Bug fortran/113503] New: [14 Regression] xtb test miscompilation starting with r14-870 jakub at gcc dot gnu.org
                   ` (7 preceding siblings ...)
  2024-02-17 15:57 ` cvs-commit at gcc dot gnu.org
@ 2024-02-17 16:14 ` jakub at gcc dot gnu.org
  8 siblings, 0 replies; 10+ messages in thread
From: jakub at gcc dot gnu.org @ 2024-02-17 16:14 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=113503

Jakub Jelinek <jakub at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
         Resolution|---                         |FIXED
             Status|ASSIGNED                    |RESOLVED

--- Comment #8 from Jakub Jelinek <jakub at gcc dot gnu.org> ---
Fixed.

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

end of thread, other threads:[~2024-02-17 16:14 UTC | newest]

Thread overview: 10+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2024-01-19 12:49 [Bug fortran/113503] New: [14 Regression] xtb test miscompilation starting with r14-870 jakub at gcc dot gnu.org
2024-01-19 12:49 ` [Bug fortran/113503] " jakub at gcc dot gnu.org
2024-01-19 16:59 ` anlauf at gcc dot gnu.org
2024-01-19 17:45 ` anlauf at gcc dot gnu.org
2024-01-20  9:00 ` pinskia at gcc dot gnu.org
2024-01-31 17:21 ` jakub at gcc dot gnu.org
2024-02-16 12:47 ` jakub at gcc dot gnu.org
2024-02-16 13:24 ` jakub at gcc dot gnu.org
2024-02-17 15:57 ` cvs-commit at gcc dot gnu.org
2024-02-17 16:14 ` jakub at gcc dot gnu.org

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).