public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/116196] New: Missing temporary with WHERE and aliasing TARGET array references
@ 2024-08-02 14:36 mikael at gcc dot gnu.org
  2024-08-02 15:52 ` [Bug fortran/116196] " mikael at gcc dot gnu.org
                   ` (2 more replies)
  0 siblings, 3 replies; 4+ messages in thread
From: mikael at gcc dot gnu.org @ 2024-08-02 14:36 UTC (permalink / raw)
  To: gcc-bugs

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

            Bug ID: 116196
           Summary: Missing temporary with WHERE and aliasing TARGET array
                    references
           Product: gcc
           Version: 14.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
          Assignee: unassigned at gcc dot gnu.org
          Reporter: mikael at gcc dot gnu.org
  Target Milestone: ---

The following example outputs:
           1           1           2           3           5
while I think it should output:
           1           1           2           4           5

I found it looking for an example exercising gfc_check_dependency with aliasing
arrays, after the analysis posted as followup to Jakub's recent pasto fix:
https://gcc.gnu.org/pipermail/gcc-patches/2024-August/658971.html


MODULE m
  IMPLICIT NONE
  INTEGER, TARGET :: arr(5)
END MODULE m

PROGRAM main
  USE m
  IMPLICIT NONE
  arr = (/ 1, 2, 3, 4, 5 /)
  CALL bar(arr)
  PRINT *, arr
  IF (ANY(arr /= (/ 1, 1, 2, 4, 5 /))) STOP 1
CONTAINS
  SUBROUTINE bar(x)
    INTEGER, TARGET :: x(:)
    WHERE (arr(1:4) < 3) x(2:5) = x(2:5) - 1
  END SUBROUTINE bar
END PROGRAM main

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

* [Bug fortran/116196] Missing temporary with WHERE and aliasing TARGET array references
  2024-08-02 14:36 [Bug fortran/116196] New: Missing temporary with WHERE and aliasing TARGET array references mikael at gcc dot gnu.org
@ 2024-08-02 15:52 ` mikael at gcc dot gnu.org
  2024-08-21 18:06 ` mikael at gcc dot gnu.org
  2024-08-21 18:11 ` mikael at gcc dot gnu.org
  2 siblings, 0 replies; 4+ messages in thread
From: mikael at gcc dot gnu.org @ 2024-08-02 15:52 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #1 from Mikael Morin <mikael at gcc dot gnu.org> ---
Draft patch:

diff --git a/gcc/fortran/dependency.cc b/gcc/fortran/dependency.cc
index 15edf1af9df..348fd562ef6 100644
--- a/gcc/fortran/dependency.cc
+++ b/gcc/fortran/dependency.cc
@@ -1253,11 +1253,8 @@ check_data_pointer_types (gfc_expr *expr1, gfc_expr
*expr2)
   if (sym1->ts.type == BT_DERIVED && sym2->ts.type == BT_DERIVED)
     return false;

-  if (sym1->attr.pointer)
-    {
-      if (gfc_compare_types (&sym1->ts, &sym2->ts))
-       return false;
-    }
+  if (gfc_compare_types (&sym1->ts, &sym2->ts))
+    return false;

   /* This is a conservative check on the components of the derived type
      if no component references have been seen.  Since we will not dig

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

* [Bug fortran/116196] Missing temporary with WHERE and aliasing TARGET array references
  2024-08-02 14:36 [Bug fortran/116196] New: Missing temporary with WHERE and aliasing TARGET array references mikael at gcc dot gnu.org
  2024-08-02 15:52 ` [Bug fortran/116196] " mikael at gcc dot gnu.org
@ 2024-08-21 18:06 ` mikael at gcc dot gnu.org
  2024-08-21 18:11 ` mikael at gcc dot gnu.org
  2 siblings, 0 replies; 4+ messages in thread
From: mikael at gcc dot gnu.org @ 2024-08-21 18:06 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #2 from Mikael Morin <mikael at gcc dot gnu.org> ---
More complete testcase:

! { dg-do run }
! { dg-additional-options "-fdump-tree-original" }
!
! PR fortran/116196

MODULE m
  IMPLICIT NONE
  INTEGER, TARGET :: arr(5)
END MODULE m

PROGRAM main
  USE m
  IMPLICIT NONE

  arr = (/ 1, 2, 3, 4, 5 /)
  CALL bar(arr)
  PRINT *, arr
  IF (ANY(arr /= (/ 1, -1, -1, 4, 5 /))) STOP 9

  arr = (/ 1, 2, 3, 4, 5 /)
  CALL bar2(arr)
  PRINT *, arr
  IF (ANY(arr /= (/ 1, -1, -1, 4, 5 /))) STOP 16

  CALL bar3((/ 1, 2, 3, 4, 5 /))
  PRINT *, arr
  IF (ANY(arr /= (/ 1, -1, -1, 4, 5 /))) STOP 23
CONTAINS
  SUBROUTINE bar(x)
    INTEGER :: x(:)
    ! Per WHERE rules, the change of X should not affect the value
    ! of the WHERE mask as the mask is evaluated before.
    WHERE (arr(1:size(x)-1) < 3) x(2:5) = -1
  END SUBROUTINE bar
  SUBROUTINE bar2(x)
    INTEGER, TARGET :: x(:)
    ! As X is TARGET, the change of ARR is allowed to affect the value of X.
    ! Still, per WHERE rules, the change of ARR does not affect the value
    ! of the WHERE mask as the mask is evaluated before.
    WHERE (x(1:size(x)-1) < 3) arr(2:5) = -1
  END SUBROUTINE bar2
  SUBROUTINE bar3(x)
    INTEGER :: x(:)
    ! As X isn't TARGET, we know that the change of ARR is not allowed to
affect
    ! the value of X.  So the WHERE mask can be evaluated on the fly, without
    ! any temporary.
    WHERE (x(1:size(x)-1) < 3) arr(2:5) = -1
  END SUBROUTINE bar3
END PROGRAM main

! Three bar functions, two using a temporary, one temporary-free.
! { dg-final { scan-tree-dump-times "__builtin_malloc" 2 "original" } }

! No memory leak
! { dg-final { scan-tree-dump-times "__builtin_free" 2 "original" } }

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

* [Bug fortran/116196] Missing temporary with WHERE and aliasing TARGET array references
  2024-08-02 14:36 [Bug fortran/116196] New: Missing temporary with WHERE and aliasing TARGET array references mikael at gcc dot gnu.org
  2024-08-02 15:52 ` [Bug fortran/116196] " mikael at gcc dot gnu.org
  2024-08-21 18:06 ` mikael at gcc dot gnu.org
@ 2024-08-21 18:11 ` mikael at gcc dot gnu.org
  2 siblings, 0 replies; 4+ messages in thread
From: mikael at gcc dot gnu.org @ 2024-08-21 18:11 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #3 from Mikael Morin <mikael at gcc dot gnu.org> ---
Created attachment 58971
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=58971&action=edit
Draft patch

This fixes the testcase.
But the testcase is by far insufficient to thoroughly check the correctness of
this patch.

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

end of thread, other threads:[~2024-08-21 18:11 UTC | newest]

Thread overview: 4+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2024-08-02 14:36 [Bug fortran/116196] New: Missing temporary with WHERE and aliasing TARGET array references mikael at gcc dot gnu.org
2024-08-02 15:52 ` [Bug fortran/116196] " mikael at gcc dot gnu.org
2024-08-21 18:06 ` mikael at gcc dot gnu.org
2024-08-21 18:11 ` mikael 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).