public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug middle-end/43340]  New: miscompiled code at -O2
@ 2010-03-12  8:13 jv244 at cam dot ac dot uk
  2010-03-12  8:14 ` [Bug middle-end/43340] " jv244 at cam dot ac dot uk
                   ` (8 more replies)
  0 siblings, 9 replies; 10+ messages in thread
From: jv244 at cam dot ac dot uk @ 2010-03-12  8:13 UTC (permalink / raw)
  To: gcc-bugs

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


^ permalink raw reply	[flat|nested] 10+ messages in thread

* [Bug middle-end/43340] miscompiled code at -O2
  2010-03-12  8:13 [Bug middle-end/43340] New: miscompiled code at -O2 jv244 at cam dot ac dot uk
@ 2010-03-12  8:14 ` jv244 at cam dot ac dot uk
  2010-03-12  8:41 ` jakub at gcc dot gnu dot org
                   ` (7 subsequent siblings)
  8 siblings, 0 replies; 10+ messages in thread
From: jv244 at cam dot ac dot uk @ 2010-03-12  8:14 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from jv244 at cam dot ac dot uk  2010-03-12 08:14 -------
Created an attachment (id=20092)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=20092&action=view)
result of -fdump-tree-all

results of -fdump-tree-all at -O1 and -O2


-- 


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


^ permalink raw reply	[flat|nested] 10+ messages in thread

* [Bug middle-end/43340] miscompiled code at -O2
  2010-03-12  8:13 [Bug middle-end/43340] New: miscompiled code at -O2 jv244 at cam dot ac dot uk
  2010-03-12  8:14 ` [Bug middle-end/43340] " jv244 at cam dot ac dot uk
@ 2010-03-12  8:41 ` jakub at gcc dot gnu dot org
  2010-03-12  9:00 ` jv244 at cam dot ac dot uk
                   ` (6 subsequent siblings)
  8 siblings, 0 replies; 10+ messages in thread
From: jakub at gcc dot gnu dot org @ 2010-03-12  8:41 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from jakub at gcc dot gnu dot org  2010-03-12 08:40 -------
What kind of dependencies?  The routine just calls one another routinem so all
you need is find out what arguments it is called with, write a small wrapper
that calls it with those arguments, and write a dummy rotint that fills in the
pre-computed arguments that haven't been passed to the whole routine.


-- 


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


^ permalink raw reply	[flat|nested] 10+ messages in thread

* [Bug middle-end/43340] miscompiled code at -O2
  2010-03-12  8:13 [Bug middle-end/43340] New: miscompiled code at -O2 jv244 at cam dot ac dot uk
  2010-03-12  8:14 ` [Bug middle-end/43340] " jv244 at cam dot ac dot uk
  2010-03-12  8:41 ` jakub at gcc dot gnu dot org
@ 2010-03-12  9:00 ` jv244 at cam dot ac dot uk
  2010-03-12 11:20 ` rguenth at gcc dot gnu dot org
                   ` (5 subsequent siblings)
  8 siblings, 0 replies; 10+ messages in thread
From: jv244 at cam dot ac dot uk @ 2010-03-12  9:00 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from jv244 at cam dot ac dot uk  2010-03-12 09:00 -------
(In reply to comment #2)
> What kind of dependencies?  

all derived types, defined in various modules, each with further dependencies,
and the objects that are module variables.

> The routine just calls one another routinem so all
> you need is find out what arguments it is called with, write a small wrapper
> that calls it with those arguments, and write a dummy rotint that fills in the
> pre-computed arguments that haven't been passed to the whole routine.

More difficult than it might seem, unfortunately, but possible of course.


-- 


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


^ permalink raw reply	[flat|nested] 10+ messages in thread

* [Bug middle-end/43340] miscompiled code at -O2
  2010-03-12  8:13 [Bug middle-end/43340] New: miscompiled code at -O2 jv244 at cam dot ac dot uk
                   ` (2 preceding siblings ...)
  2010-03-12  9:00 ` jv244 at cam dot ac dot uk
@ 2010-03-12 11:20 ` rguenth at gcc dot gnu dot org
  2010-03-12 11:41 ` jv244 at cam dot ac dot uk
                   ` (4 subsequent siblings)
  8 siblings, 0 replies; 10+ messages in thread
From: rguenth at gcc dot gnu dot org @ 2010-03-12 11:20 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from rguenth at gcc dot gnu dot org  2010-03-12 11:20 -------
Candidates to try for -O1 vs. -O2 are -f[no-]tree-vrp, -f[no-]tree-pre,
-f[no-]strict-aliasing.  You can also rule out inlining effects by
-fno-inline.


-- 


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


^ permalink raw reply	[flat|nested] 10+ messages in thread

* [Bug middle-end/43340] miscompiled code at -O2
  2010-03-12  8:13 [Bug middle-end/43340] New: miscompiled code at -O2 jv244 at cam dot ac dot uk
                   ` (3 preceding siblings ...)
  2010-03-12 11:20 ` rguenth at gcc dot gnu dot org
@ 2010-03-12 11:41 ` jv244 at cam dot ac dot uk
  2010-03-12 11:46 ` rguenth at gcc dot gnu dot org
                   ` (3 subsequent siblings)
  8 siblings, 0 replies; 10+ messages in thread
From: jv244 at cam dot ac dot uk @ 2010-03-12 11:41 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from jv244 at cam dot ac dot uk  2010-03-12 11:41 -------
(In reply to comment #4)
> Candidates to try for -O1 vs. -O2 are -f[no-]tree-vrp, -f[no-]tree-pre,
> -f[no-]strict-aliasing.  You can also rule out inlining effects by
> -fno-inline.

no luck :-(

-O1 OK
-O2 BUG
-O2 -fno-inline BUG
-O2 -fno-inline -fno-tree-vrp BUG
-O2 -fno-inline -fno-tree-vrp -fno-tree-pre BUG
-O2 -fno-inline -fno-tree-vrp -fno-tree-pre -fstrict-aliasing BUG
-O1 -ftree-vrp -ftree-pre -fno-strict-aliasing OK


-- 


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


^ permalink raw reply	[flat|nested] 10+ messages in thread

* [Bug middle-end/43340] miscompiled code at -O2
  2010-03-12  8:13 [Bug middle-end/43340] New: miscompiled code at -O2 jv244 at cam dot ac dot uk
                   ` (4 preceding siblings ...)
  2010-03-12 11:41 ` jv244 at cam dot ac dot uk
@ 2010-03-12 11:46 ` rguenth at gcc dot gnu dot org
  2010-03-12 12:01 ` jv244 at cam dot ac dot uk
                   ` (2 subsequent siblings)
  8 siblings, 0 replies; 10+ messages in thread
From: rguenth at gcc dot gnu dot org @ 2010-03-12 11:46 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from rguenth at gcc dot gnu dot org  2010-03-12 11:46 -------
-O2 -fno-inline -fno-tree-vrp -fno-tree-pre -fno-strict-aliasing

?  You can also try -fno-ipa-cp and/or -fno-strict-overflow


-- 


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


^ permalink raw reply	[flat|nested] 10+ messages in thread

* [Bug middle-end/43340] miscompiled code at -O2
  2010-03-12  8:13 [Bug middle-end/43340] New: miscompiled code at -O2 jv244 at cam dot ac dot uk
                   ` (5 preceding siblings ...)
  2010-03-12 11:46 ` rguenth at gcc dot gnu dot org
@ 2010-03-12 12:01 ` jv244 at cam dot ac dot uk
  2010-03-12 12:35 ` jv244 at cam dot ac dot uk
  2010-03-12 14:20 ` rguenth at gcc dot gnu dot org
  8 siblings, 0 replies; 10+ messages in thread
From: jv244 at cam dot ac dot uk @ 2010-03-12 12:01 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #7 from jv244 at cam dot ac dot uk  2010-03-12 12:01 -------
> ?  You can also try -fno-ipa-cp and/or -fno-strict-overflow

-O2 -fno-inline -fno-tree-vrp -fno-tree-pre -fno-strict-aliasing -fno-ipa-cp
BUG
-O2 -fno-inline -fno-tree-vrp -fno-tree-pre -fno-strict-aliasing -fno-ipa-cp
-fno-strict-overflow BUG

If I add the write statement:

write(999,*) i,j,k,l,a,aa,bb

in the inner loop, the bug also disappears at -O2.


-- 


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


^ permalink raw reply	[flat|nested] 10+ messages in thread

* [Bug middle-end/43340] miscompiled code at -O2
  2010-03-12  8:13 [Bug middle-end/43340] New: miscompiled code at -O2 jv244 at cam dot ac dot uk
                   ` (6 preceding siblings ...)
  2010-03-12 12:01 ` jv244 at cam dot ac dot uk
@ 2010-03-12 12:35 ` jv244 at cam dot ac dot uk
  2010-03-12 14:20 ` rguenth at gcc dot gnu dot org
  8 siblings, 0 replies; 10+ messages in thread
From: jv244 at cam dot ac dot uk @ 2010-03-12 12:35 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #8 from jv244 at cam dot ac dot uk  2010-03-12 12:35 -------
looks like this rather is a bug in CP2K. fi_mat and fj_mat can alias... So,
I'll close this bug, but it is worthwhile to note that -fno-strict-aliasing did
not 'fix' this problem. 


-- 

jv244 at cam dot ac dot uk changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |RESOLVED
         Resolution|                            |FIXED


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


^ permalink raw reply	[flat|nested] 10+ messages in thread

* [Bug middle-end/43340] miscompiled code at -O2
  2010-03-12  8:13 [Bug middle-end/43340] New: miscompiled code at -O2 jv244 at cam dot ac dot uk
                   ` (7 preceding siblings ...)
  2010-03-12 12:35 ` jv244 at cam dot ac dot uk
@ 2010-03-12 14:20 ` rguenth at gcc dot gnu dot org
  8 siblings, 0 replies; 10+ messages in thread
From: rguenth at gcc dot gnu dot org @ 2010-03-12 14:20 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #9 from rguenth at gcc dot gnu dot org  2010-03-12 14:20 -------
(In reply to comment #8)
> looks like this rather is a bug in CP2K. fi_mat and fj_mat can alias... So,
> I'll close this bug, but it is worthwhile to note that -fno-strict-aliasing did
> not 'fix' this problem. 

-fno-strict-aliasing only affects type-based alias analysis, not analysis
based on restrict qualification or flag_argument_noalias (which the Fortran
frontend sets).


-- 


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


^ permalink raw reply	[flat|nested] 10+ messages in thread

end of thread, other threads:[~2010-03-12 14:20 UTC | newest]

Thread overview: 10+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2010-03-12  8:13 [Bug middle-end/43340] New: miscompiled code at -O2 jv244 at cam dot ac dot uk
2010-03-12  8:14 ` [Bug middle-end/43340] " jv244 at cam dot ac dot uk
2010-03-12  8:41 ` jakub at gcc dot gnu dot org
2010-03-12  9:00 ` jv244 at cam dot ac dot uk
2010-03-12 11:20 ` rguenth at gcc dot gnu dot org
2010-03-12 11:41 ` jv244 at cam dot ac dot uk
2010-03-12 11:46 ` rguenth at gcc dot gnu dot org
2010-03-12 12:01 ` jv244 at cam dot ac dot uk
2010-03-12 12:35 ` jv244 at cam dot ac dot uk
2010-03-12 14:20 ` rguenth at gcc dot gnu dot org

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).