as mentioned in the CP2K PR 29975, current trunk miscompiles CP2K at -O2. the
following illustrates the issue:

MODULE TEST
  IMPLICIT NONE
  INTEGER, PARAMETER :: dp=KIND(0.0D0)
  TYPE mulliken_restraint_type
    INTEGER                         :: ref_count
    REAL(KIND = dp)                 :: strength
    REAL(KIND = dp)                 :: TARGET
    INTEGER                         :: natoms
    INTEGER, POINTER, DIMENSION(:)  :: atoms
  END TYPE mulliken_restraint_type
CONTAINS
  SUBROUTINE INIT(mulliken)
   TYPE(mulliken_restraint_type), INTENT(INOUT) :: mulliken
   ALLOCATE(mulliken%atoms(1))
   mulliken%atoms(1)=1
   mulliken%natoms=1
   mulliken%target=0
   mulliken%strength=0
  END SUBROUTINE INIT
  SUBROUTINE restraint_functional(mulliken_restraint_control,charges, &
                                charges_deriv,energy,order_p)
    TYPE(mulliken_restraint_type), &
      INTENT(IN)                             :: mulliken_restraint_control
    REAL(KIND=dp), DIMENSION(:, :), POINTER  :: charges, charges_deriv
    REAL(KIND=dp), INTENT(OUT)               :: energy, order_p

    INTEGER                                  :: I
    REAL(KIND=dp)                            :: dum

    charges_deriv=0.0_dp
    order_p=0.0_dp

    DO I=1,mulliken_restraint_control%natoms
       order_p=order_p+charges(mulliken_restraint_control%atoms(I),1) &
                      -charges(mulliken_restraint_control%atoms(I),2)
    ENDDO
   
energy=mulliken_restraint_control%strength*(order_p-mulliken_restraint_control%target)**2
   
dum=2*mulliken_restraint_control%strength*(order_p-mulliken_restraint_control%target)
    DO I=1,mulliken_restraint_control%natoms
       charges_deriv(mulliken_restraint_control%atoms(I),1)=  dum
       charges_deriv(mulliken_restraint_control%atoms(I),2)= -dum
    ENDDO
END SUBROUTINE restraint_functional

END MODULE

    USE TEST
    IMPLICIT NONE
    TYPE(mulliken_restraint_type) :: mulliken
    REAL(KIND=dp), DIMENSION(:, :), POINTER  :: charges, charges_deriv
    REAL(KIND=dp) :: energy,order_p
    ALLOCATE(charges(1,2),charges_deriv(1,2))
    charges(1,1)=2.0_dp
    charges(1,2)=1.0_dp
    CALL INIT(mulliken)
    CALL restraint_functional(mulliken,charges,charges_deriv,energy,order_p)
    write(6,*) order_p
END

> gfortran -O2 test.f90
> ./a.out
   0.00000000000000
> gfortran -O1 test.f90
> ./a.out
   1.00000000000000

this is for:

Driving: gfortran -v -O2 test.f90 -lgfortranbegin -lgfortran -lm -shared-libgcc
Using built-in specs.
Target: x86_64-unknown-linux-gnu
Configured with: /data03/vondele/gcc_trunk/gcc/configure
--prefix=/data03/vondele/gcc_trunk/build --with-gmp=/data03/vondele/
--with-mpfr=/data03/vondele/ --enable-languages=c,fortran
Thread model: posix
gcc version 4.3.0 20070702 (experimental)

/data03/vondele/gcc_trunk/build/libexec/gcc/x86_64-unknown-linux-gnu/4.3.0/f951
test.f90 -quiet -dumpbase test.f90 -mtune=generic -auxbase test -O2 -version
-fintrinsic-modules-path
/data03/vondele/gcc_trunk/build/lib/gcc/x86_64-unknown-linux-gnu/4.3.0/finclude
-o /tmp/ccaqj3g7.s
GNU F95 version 4.3.0 20070702 (experimental) (x86_64-unknown-linux-gnu)
        compiled by GNU C version 4.3.0 20070702 (experimental), GMP version
4.2.1, MPFR version 2.2.1.
GGC heuristics: --param ggc-min-expand=30 --param ggc-min-heapsize=4096
 as -V -Qy -o /tmp/cccJhUbb.o /tmp/ccaqj3g7.s
GNU assembler version 2.16.91.0.5 (x86_64-suse-linux) using BFD version
2.16.91.0.5 20051219 (SUSE Linux)

/data03/vondele/gcc_trunk/build/libexec/gcc/x86_64-unknown-linux-gnu/4.3.0/collect2
--eh-frame-hdr -m elf_x86_64 -dynamic-linker /lib64/ld-linux-x86-64.so.2
/usr/lib/../lib64/crt1.o /usr/lib/../lib64/crti.o
/data03/vondele/gcc_trunk/build/lib/gcc/x86_64-unknown-linux-gnu/4.3.0/crtbegin.o
-L/data03/vondele/gcc_trunk/build/lib/gcc/x86_64-unknown-linux-gnu/4.3.0
-L/data03/vondele/gcc_trunk/build/lib/gcc/x86_64-unknown-linux-gnu/4.3.0/../../../../lib64
-L/lib/../lib64 -L/usr/lib/../lib64
-L/data03/vondele/gcc_trunk/build/lib/gcc/x86_64-unknown-linux-gnu/4.3.0/../../..
/tmp/cccJhUbb.o -lgfortranbegin -lgfortran -lm -lgcc_s -lgcc -lc -lgcc_s -lgcc
/data03/vondele/gcc_trunk/build/lib/gcc/x86_64-unknown-linux-gnu/4.3.0/crtend.o
/usr/lib/../lib64/crtn.o


-- 
           Summary: miscompilation at -O2
           Product: gcc
           Version: 4.3.0
            Status: UNCONFIRMED
          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=32604

Reply via email to