compiling the testcase below with

gfortran -O3 -fbounds-check 

yields under 'valgrind --tool=memcheck ./a.out'

 ==23130==
==23130== Conditional jump or move depends on uninitialised value(s)
==23130==    at 0x4008BD: __m1_MOD_cp_fm_upper_to_full (in
/data03/vondele/bugs/ttt/a.out)
==23130==    by 0x400FD7: MAIN__ (in /data03/vondele/bugs/ttt/a.out)
==23130==    by 0x401059: main (fmain.c:21)
==23130==
==23130== ERROR SUMMARY: 16 errors from 1 contexts (suppressed: 3 from 1)

the valgrind error is absent if '-O2 -fbounds-check' is being employed.

This happens with trunk as well as older versions.

Testcase:

MODULE M1
  INTEGER, PARAMETER :: sp=4, dp=8
  TYPE cp_fm_type
     REAL(KIND=sp), DIMENSION(:,:), POINTER :: local_data_sp
     REAL(KIND=dp), DIMENSION(:,:), POINTER :: local_data
     INTEGER :: nrow_global,ncol_global
     LOGICAL :: use_sp
  END TYPE
CONTAINS
  SUBROUTINE cp_fm_upper_to_full(matrix,work)
    TYPE(cp_fm_type), POINTER          :: matrix,work
    INTEGER :: irow_global, ncol_global, nrow_global
    REAL(KIND = dp), DIMENSION(:,:), POINTER :: a
    REAL(KIND = sp), DIMENSION(:,:), POINTER :: a_sp

    nrow_global=matrix%nrow_global
    ncol_global=matrix%ncol_global
    a => matrix%local_data
    a_sp => matrix%local_data_sp

    DO irow_global=1,nrow_global
       DO icol_global=irow_global+1,ncol_global
          IF(matrix%use_sp) THEN
             a_sp(icol_global,irow_global)=a_sp(irow_global,icol_global)
          ELSE
             a(icol_global,irow_global)=a(irow_global,icol_global)
          ENDIF
       ENDDO
    ENDDO
  END SUBROUTINE cp_fm_upper_to_full
END MODULE M1

  USE M1
  TYPE(cp_fm_type), POINTER :: a,b
  INTEGER :: N
  N=17
  ALLOCATE(a,b)
  ALLOCATE(a%local_data(N,N),b%local_data(N,N))
  a%nrow_global=N
  a%ncol_global=N
  b%nrow_global=N
  b%ncol_global=N
  a%use_sp=.FALSE.
  b%use_sp=.FALSE.
  a%local_data=0
  CALL cp_fm_upper_to_full(a,b)
END


-- 
           Summary: wrong code with -O3 -fbounds-check
           Product: gcc
           Version: 4.6.0
            Status: UNCONFIRMED
          Keywords: wrong-code
          Severity: normal
          Priority: P3
         Component: middle-end
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: jv244 at cam dot ac dot uk


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

Reply via email to