This is the mail archive of the gcc-bugs@gcc.gnu.org mailing list for the GCC project.


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]
Other format: [Raw text]

[Bug fortran/38863] New: WHERE with multiple elemental defined assignments gives wrong answer


The following program gives the wrong answers from the WHERE block.  The
expected answers are in the tda2l array.  The problem seems to be an
interaction between the dimension statements, the defined logical assignment
and the defined integer assignment statement in the WHERE block.  

The defined assignment to the logical component of TLA2L is correct (it's
effectively a do nothing assignment, since the left and right hand sides are
the same elements).  The defined assignment to the integer component is wrong. 
Changing the dimension of TDA2L from (3,2) to (nf3,nf2) gives a different
incorrect answer.  (TDA2L is not used in any of the computations, it's just a
handy way to keep track of the expected answer).  Changing the dimension of
TLA2L from (nf3,nf2) to (3,2) fixes the problem.  Commenting out the assignment
to TLA2L%L in the WHERE gives the correct answer.

Dick Hendrickson


      module rg0045_stuff

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


      TYPE UNSEQ

        INTEGER                       ::  I
        LOGICAL                       ::  L

      END TYPE UNSEQ       

      INTERFACE ASSIGNMENT(=)
        MODULE PROCEDURE L_TO_T,   I_TO_T
      END INTERFACE ASSIGNMENT(=)

      contains

        PURE ELEMENTAL SUBROUTINE Z_TO_T(OUT,ZIN)
        COMPLEX,INTENT(IN)  ::  ZIN
        INTEGER,INTENT(IN)  ::  IIN
        LOGICAL,INTENT(IN)  ::  LIN
        TYPE (UNSEQ), INTENT(INOUT) ::  OUT

        OUT%i = -99
        RETURN

        ENTRY I_TO_T(OUT,IIN)
        OUT%I = IIN
        RETURN

        ENTRY L_TO_T(OUT,LIN)
        OUT%L = LIN
        RETURN

        END SUBROUTINE


      SUBROUTINE RG0045(nf1,nf2,nf3)

      TYPE(UNSEQ) TLA2L(nf3,nf2)   !changing dimension to (3,2) fixes problem
      TYPE(UNSEQ) TDA2L(3,2)       !changing dimension to (nf3,nf2) changes
output
      logical  lda(nf3,nf2)

!expected results
      tda2l(1:3,1)%l = (/.true.,.false.,.true./)
      tda2l(1:3,2)%l = (/.false.,.true.,.false./)
      tda2l(1:3,1)%i = (/1,-1,3/)
      tda2l(1:3,2)%i = (/-1,5,-1/)


      lda = tda2l%l

      tLa2l%l = lda
      tLa2l(1:3,1)%i = (/1,2,3/)
      tLa2l(1:3,2)%i = (/4,5,6/)


      WHERE(LDA)
        TLA2L = TLA2L(1:3,1:2)%L     !removing this line fixes problem
        TLA2L = TLA2L(1:3,1:2)%I
      ELSEWHERE
        TLA2L = -1
      ENDWHERE

      print *, tla2l%i
      print *, tda2l%i

      print *, tla2l%l
      print *, tda2l%l

      END SUBROUTINE
      end module rg0045_stuff

      program try_rg0045
      use rg0045_stuff

      call rg0045(1,2,3)

      end

from the above program
C:gfortran>gfortran try_rg0045.f
C:\gfortran>a
           3          -1        8192          -1           0          -1
           1          -1           3          -1           5          -1
 T F T F T F
 T F T F T F

with the tda2l array dimensioned (nf3,nf2)
C:gfortran>gfortran try_rg0045.f

C:\gfortran>a
           0          -1     4063608          -1          -1          -1
           1          -1           3          -1           5          -1
 T F T F T F
 T F T F T F

With the logical assignment commented out
C:gfortran>gfortran try_rg0045.f

C:\gfortran>a
           1          -1           3          -1           5          -1
           1          -1           3          -1           5          -1
 T F T F T F
 T F T F T F


with constant (3,2) array dimensions and the logical assignment left in
C:\gfortran>gfortran try_rg0045.f

C:\gfortran>a
           1          -1           3          -1           5          -1
           1          -1           3          -1           5          -1
 T F T F T F
 T F T F T F


-- 
           Summary: WHERE with multiple elemental defined assignments gives
                    wrong answer
           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=38863


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]