public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/37723]  New: wrong result for left-right hand side array overlap and (possibly) negative strides
@ 2008-10-02 22:11 dick dot hendrickson at gmail dot com
  2008-10-05 13:04 ` [Bug fortran/37723] " dominiq at lps dot ens dot fr
                   ` (9 more replies)
  0 siblings, 10 replies; 11+ messages in thread
From: dick dot hendrickson at gmail dot com @ 2008-10-02 22:11 UTC (permalink / raw)
  To: gcc-bugs

Thee following program gives wrong results for some of the array
elements in an assignment when there is an overlap between the
left hand and right hand arrays.  The errors sometimes move around
as I modified the code (although I've changed enough things that 
I can't reproduce different failures.  Changing the U* variables
from arrays of structures to scalar structures (still with an
array component) makes the errors go away.

Dick Hendrickson

! fails on Windows XP
! gcc version 4.4.0 20080603 (experimental) [trunk revision 136333] (GCC)

!Gives wrong answers for tests 1 and 3
!Gives correct answers if the dimensions of the various U arrays are removed
!
! The errors sometimes change as I moved code around to isolate a test case

! I have other similar tests with a left-right hand side overlap (and often
! negative strides) that fail in the large, but work when reduced to
! a simple subroutine.

      module cg0071_mod
      type seq
          integer ia(10,10)
      end type
      contains

      SUBROUTINE CGAM02(UDA,nf3,nf9,nf10,nf1,mf1)
      TYPE (SEQ)  ::  UDA(4)
      UDA(  3)%IA(  1:  9,      1:  10) =
     $UDA(  3)%IA(  9:  1:-1,  10:  1:-1)+1
      END SUBROUTINE

      end module

      program try_cg0071
      use cg0071_mod
      TYPE(SEQ) UDA1L(4)
      TYPE(SEQ) UDA1R(4)
      type(seq) utest(4)

      do j1 = 1,10
        do j2 = 1,10
           uda1r%ia(j1,j2) = j1 + 10*(j2-1)
           uda1l%ia(j1,j2) = 10000 + uda1r%ia(j1,j2)
        enddo
      enddo

      call cg0071(uda1l,uda1r,4)

      end

      SUBROUTINE CG0071(UDA1L,UDA1R,nf4)
!  COPYRIGHT 1999   SPACKMAN & HENDRICKSON, INC.

      use cg0071_mod
      TYPE(SEQ) UDA1L(4)
      TYPE(SEQ) UDA1R(4)
      type(seq) utest(4)
      type(seq) uda(4)

      UDA1L = UDA1R
      utest = uda1r
      uda = uda1r

      CALL CGAM02(UDA1L,3,9,10,1,-1)         !1st test

      Utest(  3)%IA(  1:  9,      1:  10) =      !2nd test
     $UDA1r(  3)%IA(  9:  1:-1,  10:  1:-1)+1

      UDA(  3)%IA(  1:  9,      1:  10) =        !3rd test
     $UDA(  3)%IA(  9:  1:-1,  10:  1:-1)+1

      print *,'                           expected      actual'
      print *, 'first test same dummy arg on left and right'
      DO J1 = 1,9
      DO J2 = 1,10
      if (UDA1R(3)%IA(10-J1,11-j2)+1 
     $/=  UDA1L(3)%IA(J1,J2)) 
     $     print *, j1, j2, uda1r(3)% ia(10-J1,11-j2)+1 , 
     $UDA1L(3)%IA(J1,J2)
      ENDDO; ENDDO

      print *, 'second test different arrays on left and right'
      DO J1 = 1,9
      DO J2 = 1,10
      if (UDA1R(3)%IA(10-J1,11-j2)+1 
     $/=  Utest(3)%IA(J1,J2)) 
     $     print *, j1, j2, uda1r(3)% ia(10-J1,11-j2)+1 , 
     $Utest(3)%IA(J1,J2)
      ENDDO; ENDDO

      print *, 'third test, same local array on left and right'
      DO J1 = 1,9
      DO J2 = 1,10
      if (UDA1R(3)%IA(10-J1,11-j2)+1 
     $/=  Uda(3)%IA(J1,J2)) 
     $     print *, j1, j2, uda1r(3)% ia(10-J1,11-j2)+1 , 
     $Uda(3)%IA(J1,J2)
      ENDDO; ENDDO
      END SUBROUTINE

C:\gfortran>gfortran cg0071.f

C:\documents and settings\s and h\my documents\g_experiments\gfortran>a
                            expected      actual
 first test same dummy arg on left and right
           1           6          50          53
           1           7          40          63
           1           8          30          73
           1           9          20          83
           1          10          10          93
           2           6          49          54
           2           7          39          64
           2           8          29          74
           2           9          19          84
           2          10           9          94
           3           6          48          55
           3           7          38          65
           3           8          28          75
           3           9          18          85
           3          10           8          95
           4           6          47          56
           4           7          37          66
           4           8          27          76
           4           9          17          86
           4          10           7          96
           5           6          46          57
           5           7          36          67
           5           8          26          77
           5           9          16          87
           5          10           6          97
           6           6          45          58
           6           7          35          68
           6           8          25          78
           6           9          15          88
           6          10           5          98
           7           6          44          59
           7           7          34          69
           7           8          24          79
           7           9          14          89
           7          10           4          99
           8           6          43          60
           8           7          33          70
           8           8          23          80
           8           9          13          90
           8          10           3         100
           9           6          42          61
           9           7          32          71
           9           8          22          81
           9           9          12          91
           9          10           2         101
 second test different arrays on left and right
 third test, same local array on left and right
           1           6          50          53
           1           7          40          63
           1           8          30          73
           1           9          20          83
           1          10          10          93
           2           6          49          54
           2           7          39          64
           2           8          29          74
           2           9          19          84
           2          10           9          94
           3           6          48          55
           3           7          38          65
           3           8          28          75
           3           9          18          85
           3          10           8          95
           4           6          47          56
           4           7          37          66
           4           8          27          76
           4           9          17          86
           4          10           7          96
           5           6          46          57
           5           7          36          67
           5           8          26          77
           5           9          16          87
           5          10           6          97
           6           6          45          58
           6           7          35          68
           6           8          25          78
           6           9          15          88
           6          10           5          98
           7           6          44          59
           7           7          34          69
           7           8          24          79
           7           9          14          89
           7          10           4          99
           8           6          43          60
           8           7          33          70
           8           8          23          80
           8           9          13          90
           8          10           3         100
           9           6          42          61
           9           7          32          71
           9           8          22          81
           9           9          12          91
           9          10           2         101


-- 
           Summary: wrong result for left-right hand side array overlap and
                    (possibly) negative strides
           Product: gcc
           Version: 4.4.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: dick dot hendrickson at gmail dot com


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=37723


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

* [Bug fortran/37723] wrong result for left-right hand side array overlap and (possibly) negative strides
  2008-10-02 22:11 [Bug fortran/37723] New: wrong result for left-right hand side array overlap and (possibly) negative strides dick dot hendrickson at gmail dot com
@ 2008-10-05 13:04 ` dominiq at lps dot ens dot fr
  2008-10-05 17:29 ` jvdelisle at gcc dot gnu dot org
                   ` (8 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: dominiq at lps dot ens dot fr @ 2008-10-05 13:04 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from dominiq at lps dot ens dot fr  2008-10-05 13:03 -------
Confirmed on (powerpc|i686)-apple-darwin9. Since gfortran produces a wrong
code, I think the "severity" should be increased to "major" or even "critical".


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=37723


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

* [Bug fortran/37723] wrong result for left-right hand side array overlap and (possibly) negative strides
  2008-10-02 22:11 [Bug fortran/37723] New: wrong result for left-right hand side array overlap and (possibly) negative strides dick dot hendrickson at gmail dot com
  2008-10-05 13:04 ` [Bug fortran/37723] " dominiq at lps dot ens dot fr
@ 2008-10-05 17:29 ` jvdelisle at gcc dot gnu dot org
  2008-10-06  8:35 ` dominiq at lps dot ens dot fr
                   ` (7 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: jvdelisle at gcc dot gnu dot org @ 2008-10-05 17:29 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from jvdelisle at gcc dot gnu dot org  2008-10-05 17:28 -------
Confirmed on 4.3 and 4.1.2 so not a regression.


-- 

jvdelisle at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Severity|normal                      |major
             Status|UNCONFIRMED                 |NEW
     Ever Confirmed|0                           |1
   Last reconfirmed|0000-00-00 00:00:00         |2008-10-05 17:28:19
               date|                            |


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=37723


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

* [Bug fortran/37723] wrong result for left-right hand side array overlap and (possibly) negative strides
  2008-10-02 22:11 [Bug fortran/37723] New: wrong result for left-right hand side array overlap and (possibly) negative strides dick dot hendrickson at gmail dot com
  2008-10-05 13:04 ` [Bug fortran/37723] " dominiq at lps dot ens dot fr
  2008-10-05 17:29 ` jvdelisle at gcc dot gnu dot org
@ 2008-10-06  8:35 ` dominiq at lps dot ens dot fr
  2008-10-12 11:31 ` tkoenig at gcc dot gnu dot org
                   ` (6 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: dominiq at lps dot ens dot fr @ 2008-10-06  8:35 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from dominiq at lps dot ens dot fr  2008-10-06 08:34 -------
Reduced test case:

      program try_cg0071
      type seq
          integer ia(10)
      end type
      TYPE(SEQ) UDA1R
      type(seq) uda(1)

      do j1 = 1,10
        uda1r%ia(j1) = j1
      enddo

      uda = uda1r
      UDA(1)%IA(1:9) = UDA(1)%IA(9:1:-1)+1

      DO J1 = 1,9
         if (UDA1R%IA(10-J1)+1 /=  Uda(1)%IA(J1)) call abort()
      ENDDO

      end

The test does not fail if UDA is not an array.


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=37723


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

* [Bug fortran/37723] wrong result for left-right hand side array overlap and (possibly) negative strides
  2008-10-02 22:11 [Bug fortran/37723] New: wrong result for left-right hand side array overlap and (possibly) negative strides dick dot hendrickson at gmail dot com
                   ` (2 preceding siblings ...)
  2008-10-06  8:35 ` dominiq at lps dot ens dot fr
@ 2008-10-12 11:31 ` tkoenig at gcc dot gnu dot org
  2008-10-13 19:59 ` pault at gcc dot gnu dot org
                   ` (5 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: tkoenig at gcc dot gnu dot org @ 2008-10-12 11:31 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from tkoenig at gcc dot gnu dot org  2008-10-12 11:30 -------
Paul, I'd like to draw your attention to this one.  If you have any cycles to
spare right now...


-- 

tkoenig at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |pault at gcc dot gnu dot
                   |                            |org, tkoenig at gcc dot gnu
                   |                            |dot org


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=37723


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

* [Bug fortran/37723] wrong result for left-right hand side array overlap and (possibly) negative strides
  2008-10-02 22:11 [Bug fortran/37723] New: wrong result for left-right hand side array overlap and (possibly) negative strides dick dot hendrickson at gmail dot com
                   ` (3 preceding siblings ...)
  2008-10-12 11:31 ` tkoenig at gcc dot gnu dot org
@ 2008-10-13 19:59 ` pault at gcc dot gnu dot org
  2008-10-15  9:21 ` pault at gcc dot gnu dot org
                   ` (4 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: pault at gcc dot gnu dot org @ 2008-10-13 19:59 UTC (permalink / raw)
  To: gcc-bugs

[-- Warning: decoded text below may be mangled, UTF-8 assumed --]
[-- Attachment #1: Type: text/plain, Size: 846 bytes --]



------- Comment #5 from pault at gcc dot gnu dot org  2008-10-13 19:57 -------
(In reply to comment #4)
> Paul, I'd like to draw your attention to this one.  If you have any cycles to
> spare right now...

Hi Thomas,

I suspect that it has a lot to do with PR37787, which I just fixed.

I´m on to it!

Paul


-- 

pault at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
         AssignedTo|unassigned at gcc dot gnu   |pault at gcc dot gnu dot org
                   |dot org                     |
             Status|NEW                         |ASSIGNED
   Last reconfirmed|2008-10-05 17:28:19         |2008-10-13 19:57:57
               date|                            |


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=37723


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

* [Bug fortran/37723] wrong result for left-right hand side array overlap and (possibly) negative strides
  2008-10-02 22:11 [Bug fortran/37723] New: wrong result for left-right hand side array overlap and (possibly) negative strides dick dot hendrickson at gmail dot com
                   ` (4 preceding siblings ...)
  2008-10-13 19:59 ` pault at gcc dot gnu dot org
@ 2008-10-15  9:21 ` pault at gcc dot gnu dot org
  2008-10-15 14:34 ` dominiq at lps dot ens dot fr
                   ` (3 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: pault at gcc dot gnu dot org @ 2008-10-15  9:21 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from pault at gcc dot gnu dot org  2008-10-15 09:20 -------
Created an attachment (id=16504)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=16504&action=view)
A fix for the PR

The attachment is neither boostrapped nor regtested but does fix the PR.

I am not able to do anything with it until Sunday, at least.  If anybody wishes
to take it up, please do so.

Paul


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=37723


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

* [Bug fortran/37723] wrong result for left-right hand side array overlap and (possibly) negative strides
  2008-10-02 22:11 [Bug fortran/37723] New: wrong result for left-right hand side array overlap and (possibly) negative strides dick dot hendrickson at gmail dot com
                   ` (5 preceding siblings ...)
  2008-10-15  9:21 ` pault at gcc dot gnu dot org
@ 2008-10-15 14:34 ` dominiq at lps dot ens dot fr
  2008-10-19 12:53 ` pault at gcc dot gnu dot org
                   ` (2 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: dominiq at lps dot ens dot fr @ 2008-10-15 14:34 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #7 from dominiq at lps dot ens dot fr  2008-10-15 14:33 -------
The patch on comment #6 works as advertised without regression
(i686-apple-darwin9).

Thanks for the patch.


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=37723


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

* [Bug fortran/37723] wrong result for left-right hand side array overlap and (possibly) negative strides
  2008-10-02 22:11 [Bug fortran/37723] New: wrong result for left-right hand side array overlap and (possibly) negative strides dick dot hendrickson at gmail dot com
                   ` (6 preceding siblings ...)
  2008-10-15 14:34 ` dominiq at lps dot ens dot fr
@ 2008-10-19 12:53 ` pault at gcc dot gnu dot org
  2008-10-19 12:59 ` pault at gcc dot gnu dot org
  2008-10-19 14:36 ` pault at gcc dot gnu dot org
  9 siblings, 0 replies; 11+ messages in thread
From: pault at gcc dot gnu dot org @ 2008-10-19 12:53 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #8 from pault at gcc dot gnu dot org  2008-10-19 12:52 -------
Subject: Bug 37723

Author: pault
Date: Sun Oct 19 12:51:06 2008
New Revision: 141221

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=141221
Log:
2008-10-19  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/37723
        * dependency.c (gfc_dep_resolver ): If we find equal array
        element references, go on to the next reference.

2008-10-19  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/37723
        * gfortran.dg/dependency_22.f90: New test.

Added:
    trunk/gcc/testsuite/gfortran.dg/dependency_22.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/dependency.c
    trunk/gcc/testsuite/ChangeLog


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=37723


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

* [Bug fortran/37723] wrong result for left-right hand side array overlap and (possibly) negative strides
  2008-10-02 22:11 [Bug fortran/37723] New: wrong result for left-right hand side array overlap and (possibly) negative strides dick dot hendrickson at gmail dot com
                   ` (7 preceding siblings ...)
  2008-10-19 12:53 ` pault at gcc dot gnu dot org
@ 2008-10-19 12:59 ` pault at gcc dot gnu dot org
  2008-10-19 14:36 ` pault at gcc dot gnu dot org
  9 siblings, 0 replies; 11+ messages in thread
From: pault at gcc dot gnu dot org @ 2008-10-19 12:59 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #9 from pault at gcc dot gnu dot org  2008-10-19 12:58 -------
Subject: Bug 37723

Author: pault
Date: Sun Oct 19 12:56:41 2008
New Revision: 141222

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=141222
Log:
2008-10-19  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/37723
        * dependency.c (gfc_dep_resolver ): If we find equal array
        element references, go on to the next reference.

2008-10-19  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/37723
        * gfortran.dg/dependency_22.f90: New test.

Added:
    branches/gcc-4_3-branch/gcc/testsuite/gfortran.dg/dependency_22.f90
Modified:
    branches/gcc-4_3-branch/gcc/fortran/ChangeLog
    branches/gcc-4_3-branch/gcc/fortran/dependency.c
    branches/gcc-4_3-branch/gcc/testsuite/ChangeLog


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=37723


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

* [Bug fortran/37723] wrong result for left-right hand side array overlap and (possibly) negative strides
  2008-10-02 22:11 [Bug fortran/37723] New: wrong result for left-right hand side array overlap and (possibly) negative strides dick dot hendrickson at gmail dot com
                   ` (8 preceding siblings ...)
  2008-10-19 12:59 ` pault at gcc dot gnu dot org
@ 2008-10-19 14:36 ` pault at gcc dot gnu dot org
  9 siblings, 0 replies; 11+ messages in thread
From: pault at gcc dot gnu dot org @ 2008-10-19 14:36 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #10 from pault at gcc dot gnu dot org  2008-10-19 14:34 -------
Fixed as obvious on trunk and 4.3

Paul


-- 

pault at gcc dot gnu dot org changed:

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


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=37723


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

end of thread, other threads:[~2008-10-19 14:36 UTC | newest]

Thread overview: 11+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2008-10-02 22:11 [Bug fortran/37723] New: wrong result for left-right hand side array overlap and (possibly) negative strides dick dot hendrickson at gmail dot com
2008-10-05 13:04 ` [Bug fortran/37723] " dominiq at lps dot ens dot fr
2008-10-05 17:29 ` jvdelisle at gcc dot gnu dot org
2008-10-06  8:35 ` dominiq at lps dot ens dot fr
2008-10-12 11:31 ` tkoenig at gcc dot gnu dot org
2008-10-13 19:59 ` pault at gcc dot gnu dot org
2008-10-15  9:21 ` pault at gcc dot gnu dot org
2008-10-15 14:34 ` dominiq at lps dot ens dot fr
2008-10-19 12:53 ` pault at gcc dot gnu dot org
2008-10-19 12:59 ` pault at gcc dot gnu dot org
2008-10-19 14:36 ` pault at gcc dot gnu dot 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).