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

Reply via email to