[Bug fortran/31683] New: bogus warnings / miscompilation

jv244 at cam dot ac dot uk gcc-bugzilla@gcc.gnu.org
Tue Apr 24 14:42:00 GMT 2007


The following generates bogus warnings and is likely miscompiled:

MODULE test
  IMPLICIT NONE
  INTEGER, PARAMETER :: dp=KIND(0.0D0)
  INTEGER, ALLOCATABLE, DIMENSION(:) :: ncoset
  PRIVATE

  PUBLIC :: overlap

CONTAINS

  SUBROUTINE overlap(la_max_set,la_min_set,&
                     lb_max_set,lb_min_set,&
                     s,lds,&
                     pab,force_a)
    INTEGER, INTENT(IN)                      :: la_max_set, la_min_set
    INTEGER, INTENT(IN)                      :: lb_max_set, lb_min_set
    INTEGER, INTENT(IN)                      :: lds
    REAL(KIND=dp), DIMENSION(lds, lds, *), &
      INTENT(INOUT)                          :: s
    REAL(KIND=dp), DIMENSION(:, :), &
      INTENT(IN), OPTIONAL                   :: pab
    REAL(KIND=dp), DIMENSION(3), &
      INTENT(OUT), OPTIONAL                  :: force_a

    INTEGER                                  :: i, j, k, na, nb
    LOGICAL                                  :: calculate_force_a

!   ---------------------------------------------------------------------------

        na = 0
        nb = 0
        calculate_force_a=.TRUE.
        IF (calculate_force_a) THEN
          DO k=1,3
            DO j=ncoset(lb_min_set-1)+1,ncoset(lb_max_set)
              DO i=ncoset(la_min_set-1)+1,ncoset(la_max_set)
                force_a(k) = force_a(k) + pab(na+i,nb+j)*s(i,j,k+1)
              END DO
            END DO
          END DO
        END IF

    END SUBROUTINE

END MODULE test

gfortran -c -O2 -g -Wall test.f90
test.f90: In function ‘overlap’:
test.f90:7: warning: ‘offset.4’ may be used uninitialized in this function
test.f90:7: warning: ‘stride.3’ may be used uninitialized in this function
test.f90:7: warning: ‘stride.1’ may be used uninitialized in this function
test.f90:7: warning: ‘pab.0’ may be used uninitialized in this function

it is a reduced testcase from CP2K


-- 
           Summary: bogus warnings / miscompilation
           Product: gcc
           Version: 4.3.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
        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=31683



More information about the Gcc-bugs mailing list