I find that CP2K compiled with gfortran 4.3 and 4.4 is miscompiled and produces incorrect results when compiled with '-O2' whereas '-O1' gives correct results. 4.5 is OK. At this point, I have been able to narrow it down to a single subroutine (se_fock_matrix_integrals.F):
SUBROUTINE fock2C(sepi, sepj, rij, switch, pi_tot, fi_mat, pj_tot, fj_mat, & factor, anag, se_int_control, se_taper, store_int_env, error) TYPE(semi_empirical_type), POINTER :: sepi, sepj REAL(KIND=dp), DIMENSION(3), INTENT(IN) :: rij LOGICAL, INTENT(IN) :: switch REAL(KIND=dp), DIMENSION(45, 45), & INTENT(IN) :: pi_tot REAL(KIND=dp), & DIMENSION(sepi%natorb, sepi%natorb), & INTENT(INOUT) :: fi_mat REAL(KIND=dp), DIMENSION(45, 45), & INTENT(IN) :: pj_tot REAL(KIND=dp), & DIMENSION(sepj%natorb, sepj%natorb), & INTENT(INOUT) :: fj_mat REAL(KIND=dp), INTENT(IN) :: factor LOGICAL, INTENT(IN) :: anag TYPE(se_int_control_type), INTENT(IN) :: se_int_control TYPE(se_taper_type), POINTER :: se_taper TYPE(semi_empirical_si_type), POINTER :: store_int_env TYPE(cp_error_type), INTENT(inout) :: error CHARACTER(len=*), PARAMETER :: routineN = 'fock2C', & routineP = moduleN//':'//routineN INTEGER :: i, iL, j, jL, k, kL, kr, l, & lL, natorb(2) LOGICAL :: failure REAL(KIND=dp) :: a, aa, bb, irij(3) REAL(KIND=dp), DIMENSION(2025) :: w failure = .FALSE. ! Evaluate integrals IF (.NOT.switch) THEN CALL rotint (sepi,sepj, rij,w,anag=anag,se_int_control=se_int_control,& se_taper=se_taper,store_int_env=store_int_env, error=error) ELSE irij = -rij CALL rotint (sepj,sepi,irij,w,anag=anag,se_int_control=se_int_control,& se_taper=se_taper,store_int_env=store_int_env, error=error) END IF kr = 0 natorb(1) = sepi%natorb natorb(2) = sepj%natorb IF (switch) THEN natorb(1) = sepj%natorb natorb(2) = sepi%natorb END IF DO iL = 1, natorb(1) i = se_orbital_pointer(iL) aa = 2.0_dp DO jL = 1, iL j = se_orbital_pointer(jL) IF (i == j) THEN aa = 1.0_dp END IF DO kL = 1, natorb(2) k = se_orbital_pointer(kL) bb = 2.0_dp DO lL = 1, kL l = se_orbital_pointer(lL) IF (k == l) THEN bb = 1.0_dp END IF kr = kr + 1 a = w(kr)*factor ! Coulomb IF (.NOT.switch) THEN fi_mat(i,j) = fi_mat(i,j) + bb * a * pj_tot(k,l) fj_mat(k,l) = fj_mat(k,l) + aa * a * pi_tot(i,j) fi_mat(j,i) = fi_mat(i,j) fj_mat(l,k) = fj_mat(k,l) ELSE fj_mat(i,j) = fj_mat(i,j) + bb * a * pi_tot(k,l) fi_mat(k,l) = fi_mat(k,l) + aa * a * pj_tot(i,j) fj_mat(j,i) = fj_mat(i,j) fi_mat(l,k) = fi_mat(k,l) END IF END DO END DO END DO END DO END SUBROUTINE unfortunately, due to the dependencies, getting a self-contained testcase that produces wrong results is very difficult. The only reasonable thing I have right now is build CP2K and run the test cp2k/tests/SE/regtest-3/O2.inp, and see vastly wrong total energies. I'll attach the results of -fdump-tree-all to the bug report for both -O1 and -O2, I hope that is helpful. I can easily try to see the effect of various compile options. -- Summary: miscompiled code at -O2 Product: gcc Version: 4.3.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=43340