[Bug fortran/31197] New: wrong code generated with gfortran

2007-03-16 Thread jv244 at cam dot ac dot uk
With a recent gfortran, the following compiles, but generates the wrong
results:

TYPE data
 CHARACTER(LEN=3) :: A
END TYPE
TYPE(data), DIMENSION(10), TARGET :: Z
CHARACTER(LEN=10) :: res
Z(:)%A=123
write(res,'(10A1)') TRANSPOSE(RESHAPE(Z(:)%A(2:2),(/5,2/)))
IF (res.NE.22) CALL ABORT
END


-- 
   Summary: wrong code generated with gfortran
   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=31197



[Bug fortran/31198] New: wrong code generated with gfortran

2007-03-16 Thread jv244 at cam dot ac dot uk
With a recent gfortran, the following compiles, but generates the wrong
results:

IF (T1(1.0,1.0) .NE. (1.0,1.0) ) CALL ABORT()
IF (T1(1.0) .NE. (1.0,0.0)) CALL ABORT()
IF (M1(1,2,3) .NE. 3) CALL ABORT()
IF (M1(1,2,A4=4) .NE. 4) CALL ABORT()
CONTAINS

COMPLEX FUNCTION T1(X,Y)
  REAL :: X
  REAL, OPTIONAL :: Y
  T1=CMPLX(X,Y)
END FUNCTION T1

INTEGER FUNCTION M1(A1,A2,A3,A4)
  INTEGER :: A1,A2
  INTEGER, OPTIONAL :: A3,A4
  M1=MAX(A1,A2,A3,A4)
END FUNCTION M1

END


-- 
   Summary: wrong code generated with gfortran
   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=31198



[Bug fortran/31199] New: wrong code generated with gfortran

2007-03-16 Thread jv244 at cam dot ac dot uk
With a recent gfortran, the following compiles, but generates the wrong
results:

   program write_write
   character(len=20) :: a,b,c
   write (10,(a,t1,a,a)) X, ABC, DEF
   write (10,(a,t1,a),advance='no') X, ABC
   write (10,(a)) DEF
   write (10,(a)) ABCDEFXXX
   REWIND(10)
   read(10,*) a
   read(10,*) b
   read(10,*) c
   IF (a.NE.b) CALL ABORT()
   IF (a.NE.c) CALL ABORT()
   end


-- 
   Summary: wrong code generated with gfortran
   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=31199



[Bug fortran/31200] New: wrong code generated with gfortran

2007-03-16 Thread jv244 at cam dot ac dot uk
With a recent gfortran, the following compiles, but generates the wrong
results:

  REAL,TARGET :: x
  CALL s3(f(x))
CONTAINS
  FUNCTION f(a)
REAL,POINTER :: f
REAL,TARGET :: a
f = a
  END FUNCTION
  SUBROUTINE s3(targ)
REAL,TARGET :: targ
REAL,POINTER :: p
p = targ
IF (.NOT. ASSOCIATED(p,x)) CALL ABORT()
  END SUBROUTINE
END


-- 
   Summary: wrong code generated with gfortran
   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=31200



[Bug fortran/31201] New: wrong code generated with gfortran

2007-03-16 Thread jv244 at cam dot ac dot uk
With a recent gfortran, the following compiles, but generates the wrong
results:

  integer*8  :: k=2_8**36+10
  integer*4  :: j=10
  logical  ex,op
  INQUIRE(unit=k, exist=ex,opened=op)
  IF (ex) THEN
 OPEN(unit=k)
 INQUIRE(unit=j, opened=op)
 IF (op) CALL ABORT()
  ENDIF
  end


-- 
   Summary: wrong code generated with gfortran
   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=31201



[Bug fortran/31202] New: wrong code generated with gfortran

2007-03-16 Thread jv244 at cam dot ac dot uk
With a recent gfortran, the following compiles, but generates the wrong
results:

! http://gcc.gnu.org/ml/fortran/2005-04/msg00139.html
real*8 :: a
integer*8 :: i1,i2
a=.4999444888487687421729788184165954589843750_8
i2=NINT(.4999444888487687421729788184165954589843750_8)
i1=NINT(a)
! 0.499944488848768742 0 0
write(6,'(F40.30,2I2)') a,i1,i2
IF (i1.NE.i2) CALL ABORT()
a=4503599627370497.0_8
i1=NINT(a,KIND=8)
i2=NINT(4503599627370497.0_8,KIND=8)
! 4503599627370497  4503599627370497  4503599627370497
write(6,*) 4503599627370497_8,i1,i2
IF (i1.NE.i2) CALL ABORT()
END


-- 
   Summary: wrong code generated with gfortran
   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=31202



[Bug fortran/31203] New: wrong code generated with gfortran

2007-03-16 Thread jv244 at cam dot ac dot uk
With a recent gfortran, the following compiles, but generates the wrong
results:

call s(-3)
call s(2**18)
contains
subroutine s(i)
character(LEN=I) a
IF(LEN(a).NE.MAX(0,I)) CALL ABORT()
end subroutine
end


-- 
   Summary: wrong code generated with gfortran
   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=31203



[Bug fortran/31204] New: wrong code generated with gfortran

2007-03-16 Thread jv244 at cam dot ac dot uk
With a recent gfortran, the following compiles, but generates the wrong
results:

   MODULE mod
   INTEGER, PARAMETER :: jmin(1:10) = (/ (i, i = 1, 10) /)
   CONTAINS

   SUBROUTINE one
 i = 99
   END SUBROUTINE

   SUBROUTINE two
 i=0
 CALL one
 IF (i.NE.0) CALL ABORT()
   END SUBROUTINE

   END MODULE
   USE MOD
   CALL two
   END


-- 
   Summary: wrong code generated with gfortran
   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=31204



[Bug fortran/31205] New: wrong code generated with gfortran

2007-03-16 Thread jv244 at cam dot ac dot uk
With a recent gfortran, the following compiles, but generates the wrong
results:

MODULE TT
 TYPE data_type
   INTEGER :: I=2
 END TYPE data_type
 INTERFACE ASSIGNMENT (=)
   MODULE PROCEDURE set
 END INTERFACE
CONTAINS
  PURE SUBROUTINE set(x1,x2)
TYPE(data_type), INTENT(IN) :: x2
TYPE(data_type), INTENT(OUT) :: x1
CALL S1(x1,x2)
  END SUBROUTINE
  PURE SUBROUTINE S1(x1,x2)
TYPE(data_type), INTENT(IN) :: x2
TYPE(data_type), INTENT(OUT) :: x1
x1%i=x2%i
  END SUBROUTINE
END MODULE

USE TT
TYPE(data_type) :: D,E

D%I=4
D=D

E%I=4
CALL set(E,(E))

IF (D%I.NE.4) CALL ABORT()
IF (4.NE.E%I) CALL ABORT()
END


-- 
   Summary: wrong code generated with gfortran
   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=31205



[Bug fortran/31206] New: wrong code generated with gfortran

2007-03-16 Thread jv244 at cam dot ac dot uk
With a recent gfortran, the following compiles, but generates the wrong
results:

INTEGER, PARAMETER :: K(3)=1, J(3)=2
INTEGER :: I(1)
write(6,*) MAXLOC(K,J1)
END


-- 
   Summary: wrong code generated with gfortran
   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=31206



[Bug fortran/31207] New: wrong code generated with gfortran

2007-03-16 Thread jv244 at cam dot ac dot uk
With a recent gfortran, the following compiles, but generates the wrong
results:

character(len=20) :: b
! write something no advance
open(10,FILE=fort.10,POSITION=REWIND)
write(10, '(a,t1,a)',advance='no') 'XX', 'ABC'
close(10)
! append some data
open(10,FILE=fort.10,POSITION=APPEND)
write(10, '(a)') 'DEF'
close(10)
! check what is in the first record
open(10,FILE=fort.10,POSITION=REWIND)
read(10,'(a)') b
IF (b.NE.ABCXXX) CALL ABORT()
END


-- 
   Summary: wrong code generated with gfortran
   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=31207



[Bug fortran/31208] New: wrong code generated with gfortran

2007-03-16 Thread jv244 at cam dot ac dot uk
With a recent gfortran, the following compiles, but generates the wrong
results:

SUBROUTINE S1(I,J)
character(len=I-J) :: a
IF (LEN(a)0) CALL ABORT()
END SUBROUTINE
CALL S1(1,2)
END


-- 
   Summary: wrong code generated with gfortran
   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=31208



[Bug fortran/31209] New: wrong code generated with gfortran

2007-03-16 Thread jv244 at cam dot ac dot uk
With a recent gfortran, the following compiles, but generates the wrong
results:

FUNCTION F() RESULT(RES)
 INTEGER, POINTER :: RES
 ALLOCATE(RES)
 RES=2
END FUNCTION F

SUBROUTINE S1(f,*,*)
 INTERFACE
  FUNCTION F() RESULT(RES)
   INTEGER, POINTER :: RES
  END FUNCTION F
 END INTERFACE
 RETURN F()
END SUBROUTINE

PROGRAM TEST
   INTERFACE
FUNCTION F() RESULT(RES)
 INTEGER, POINTER :: RES
END FUNCTION F
   END INTERFACE


   INTERFACE
SUBROUTINE S1(f,*,*)
  INTERFACE
   FUNCTION F() RESULT(RES)
INTEGER, POINTER :: RES
   END FUNCTION F
  END INTERFACE
 END SUBROUTINE
   END INTERFACE

   CALL S1(F,*1,*2)

   1 CONTINUE
   CALL ABORT()

   GOTO 3
   2 CONTINUE

   3 CONTINUE
END


-- 
   Summary: wrong code generated with gfortran
   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=31209



[Bug fortran/31210] New: wrong code generated with gfortran

2007-03-16 Thread jv244 at cam dot ac dot uk
With a recent gfortran, the following compiles, but generates the wrong
results:

MODULE xml_markups

   LOGICAL, PRIVATE :: should_write_tags=.TRUE.

CONTAINS

   FUNCTION write_xml_tag(tag) RESULT(res)
 CHARACTER(LEN=*), INTENT(IN) :: tag
 CHARACTER(LEN=MERGE(LEN_TRIM(tag),0,should_write_tags)) :: res
 res=tag
   END FUNCTION write_xml_tag

   SUBROUTINE set_write_xml_tags(should_write)
 LOGICAL, INTENT(IN) :: should_write
 should_write_tags=should_write
   END SUBROUTINE

END MODULE xml_markups

USE xml_markups

REAL, PARAMETER :: val=3.1415
character(len=80) :: old,new,new2

! old style write

write(old,'(T2,F12.6)')  val

! new style write
write(new,'(T2,A,F12.6,A)') write_xml_tag(keword  ), 
   val,write_xml_tag(/keyword )

! if the use has selected --no-xml-output this should be set early
CALL set_write_xml_tags(.FALSE.)

! new style write with old result
write(new2,'(T2,A,F12.6,A)') write_xml_tag(keword  ), 
   val,write_xml_tag(/keyword )

IF (old.NE.new2) CALL ABORT()

END


-- 
   Summary: wrong code generated with gfortran
   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=31210



[Bug fortran/31211] New: wrong code generated with gfortran

2007-03-16 Thread jv244 at cam dot ac dot uk
With a recent gfortran, the following compiles, but generates the wrong
results:

MODULE T
  INTERFACE cp_log
 MODULE PROCEDURE cp_logger_log
  END INTERFACE

  TYPE cp_logger_type
INTEGER :: a
  END TYPE cp_logger_type

  PUBLIC :: cp_log, cp_logger_type

CONTAINS

  SUBROUTINE cp_logger_log(logger)
TYPE(cp_logger_type), POINTER ::logger
  END SUBROUTINE

  FUNCTION cp_get_default_logger() RESULT(res)
TYPE(cp_logger_type), POINTER ::res
NULLIFY(RES)
  END FUNCTION cp_get_default_logger

END MODULE T

USE T
 CALL cp_log(cp_get_default_logger())
END


-- 
   Summary: wrong code generated with gfortran
   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=31211



[Bug fortran/31212] New: ICE on valid code with gfortran

2007-03-16 Thread jv244 at cam dot ac dot uk
A recent gfortran ICEs on the following code:

  CHARACTER(LEN=2), DIMENSION(:), POINTER :: a
  CHARACTER(LEN=4), DIMENSION(3), TARGET :: b
  b=(/,,/)
  a=b(:)(2:3)
  a=aa
  IF (ANY(b.NE.(/baab,baab,baab/))) CALL ABORT()
  END


-- 
   Summary: ICE on valid code with gfortran
   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=31212



[Bug fortran/31213] New: ICE on valid code with gfortran

2007-03-16 Thread jv244 at cam dot ac dot uk
A recent gfortran ICEs on the following code:

module mykinds
   implicit none
   integer, parameter :: ik1 = selected_int_kind(2)
   integer, parameter :: ik2 = selected_int_kind(4)
   integer, parameter :: dp = selected_real_kind(15,300)
end module mykinds

module spec_xpr
   use mykinds
   implicit none
   integer(ik2) c_size
   contains
  pure function tricky(str,ugly)
 character(*), intent(in) :: str
 integer(ik1) ia_ik1(len(str))
 interface yoagly
pure function ugly(n)
   use mykinds
   implicit none
   integer, intent(in) :: n
   complex(dp) ugly(3*n+2)
end function ugly
 end interface yoagly
 logical la(size(yoagly(size(ia_ik1
 integer i
 character(tricky_helper((/(.TRUE.,i=1,size(la))/))+c_size) tricky

 tricky = repeat('X',len(tricky))
  end function tricky

  pure function tricky_helper(lb)
 logical, intent(in) :: lb(:)
 integer tricky_helper

 tricky_helper = 2*size(lb)+3
  end function tricky_helper
end module spec_xpr

module xtra_fun
   implicit none
   contains
  pure function butt_ugly(n)
 use mykinds
 implicit none
 integer, intent(in) :: n
 complex(dp) butt_ugly(3*n+2)
 real(dp) pi, sq2

 pi = 4*atan(1.0_dp)
 sq2 = sqrt(2.0_dp)
 butt_ugly = cmplx(pi,sq2,dp)
  end function butt_ugly
end module xtra_fun

program spec_test
   use mykinds
   use spec_xpr
   use xtra_fun
   implicit none

   c_size = 5
   write(*,'(1x,i0)') len(tricky('Help me',butt_ugly))
   write(*,'(1x,a)') tricky('Help me',butt_ugly)
end program spec_test


-- 
   Summary: ICE on valid code with gfortran
   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=31213



[Bug fortran/31214] New: ICE on valid code with gfortran

2007-03-16 Thread jv244 at cam dot ac dot uk
A recent gfortran ICEs on the following code:

module type_mod
  implicit none

  type x
 integer x
  end type x
  type y
 integer x
  end type y
  type z
 integer x
  end type z

  interface assignment(=)
 module procedure equals
  end interface assignment(=)

  interface operator(//)
 module procedure a_op_b, b_op_a
  end interface operator(//)

  contains
 subroutine equals(x,y)
type(z), intent(in) :: y
type(z), intent(out) :: x

x%x = y%x
 end subroutine equals

 function a_op_b(a,b)
type(x), intent(in) :: a
type(y), intent(in) :: b
type(z) a_op_b
type(z) b_op_a
 entry b_op_a(b,a)
a_op_b%x = a%x/b%x
 end function a_op_b
end module type_mod

program test
  use type_mod
  implicit none
  type(x) :: x1 = x(19)
  type(y) :: y1 = y(7)
  type(z) z1

  z1 = x1//y1
  write(*,*) 'x1//y1 = ',z1
  z1 = y1//x1
  write(*,*) 'y1//x1 = ',z1
end program test


-- 
   Summary: ICE on valid code with gfortran
   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=31214



[Bug fortran/31215] New: ICE on valid code with gfortran

2007-03-16 Thread jv244 at cam dot ac dot uk
A recent gfortran ICEs on the following code:

module test1
   implicit none
   contains
  character(f(x)) function test2(x) result(r)
 implicit integer (x)
 dimension r(modulo(len(r)-1,3)+1)
 integer, intent(in) :: x
 interface
pure function f(x)
   integer, intent(in) :: x
   integer f
end function f
 end interface
 integer i

 do i = 1, len(r)
r(:)(i:i) = achar(mod(i,32)+iachar('@'))
 end do
  end function test2
end module test1

program test
   use test1
   implicit none

   write(*,*) len(test2(10))
   write(*,*) test2(10)
end program test

pure function f(x)
   integer, intent(in) :: x
   integer f

   f = 2*x+1
end function f


-- 
   Summary: ICE on valid code with gfortran
   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=31215



[Bug fortran/31216] New: ICE on valid code with gfortran

2007-03-16 Thread jv244 at cam dot ac dot uk
A recent gfortran ICEs on the following code:

INTEGER :: I
CHARACTER(LEN=100) :: data=1.0 3.0
REAL :: C,D
READ(data,*) C,D
I=TRANSFER(C/D,I)
SELECT CASE(I)
CASE (TRANSFER(1.0/3.0,1))
CASE DEFAULT
 CALL ABORT()
END SELECT
END


-- 
   Summary: ICE on valid code with gfortran
   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=31216



[Bug fortran/31217] New: ICE on valid code with gfortran

2007-03-16 Thread jv244 at cam dot ac dot uk
A recent gfortran ICEs on the following code:

character(LEN=12) :: b=123456789012
character(LEN=12) :: a=123456789012
FORALL(I=3:10) a(I:I+2)=a(I-2:I)
IF (a.NE.121234567890) CALL ABORT()
END


-- 
   Summary: ICE on valid code with gfortran
   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=31217



[Bug fortran/31218] New: ICE on valid code with gfortran

2007-03-16 Thread jv244 at cam dot ac dot uk
A recent gfortran ICEs on the following code:

 integer, parameter :: i=1
 real, parameter :: k=TRANSFER(i,1.0)
 integer ::  j=TRANSFER(k,i)
 character(LEN=2), parameter :: a=a 
 real, dimension(2,2), parameter :: r=1.0
 character(LEN=4) :: b=REPEAT(a,2)
 real, dimension(4) :: l=RESHAPE(r,(/4/))
 character(LEN=3) :: c=TRIM(a )

 IF (b.NE.a a ) CALL ABORT()
 IF (ANY(l.NE.1.0)) CALL ABORT()
 IF (c.NE.a  ) CALL ABORT()
 IF (j.NE.i) CALL ABORT()
 END


-- 
   Summary: ICE on valid code with gfortran
   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=31218



[Bug fortran/31219] New: ICE on valid code with gfortran

2007-03-16 Thread jv244 at cam dot ac dot uk
A recent gfortran ICEs on the following code:

INTEGER :: J
CHARACTER(LEN=8) :: str
J=3
write(str,'(2A4)') (/(F(I,J),I=1,2)/)
IF (str.NE. ODD EVE) CALL ABORT()
CONTAINS
 FUNCTION F(K,J) RESULT(I)
  INTEGER :: K,J
  CHARACTER(LEN=J) :: I
  IF (MODULO(K,2).EQ.0) THEN
 I=EVEN
  ELSE
 I=ODD
  ENDIF
 END FUNCTION
END


-- 
   Summary: ICE on valid code with gfortran
   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=31219



[Bug fortran/31220] New: ICE on valid code with gfortran

2007-03-16 Thread jv244 at cam dot ac dot uk
A recent gfortran ICEs on the following code:

CHARACTER(LEN=4), POINTER :: b
CHARACTER(LEN=10) :: r
b=F1(1,r)
b=
b=F1(2,r)
b=
b=F1(3,r)
b=
IF (r.NE.1-) CALL ABORT()
CONTAINS
FUNCTION F1(I,r) result(b)
INTEGER :: I
CHARACTER(LEN=10), TARGET, SAVE :: a=--
CHARACTER(LEN=10) :: r
CHARACTER(LEN=4), POINTER :: b
r=a
b=a(I:I+3)
END FUNCTION
END


-- 
   Summary: ICE on valid code with gfortran
   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=31220



[Bug fortran/31221] New: ICE on valid code with gfortran

2007-03-16 Thread jv244 at cam dot ac dot uk
A recent gfortran ICEs on the following code:

MODULE M1
integer, parameter :: N=10
integer, parameter :: i1(N)=(/(j,j=1,N)/)
integer, parameter :: i2(N)=MODULO(i1,5)
END MODULE M1
USE M1
k=3
select case(k)
case (i2(7))
case (i1(N-1))
end select
END


-- 
   Summary: ICE on valid code with gfortran
   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=31221



[Bug fortran/29975] [meta-bugs] ICEs with CP2K

2007-03-16 Thread jv244 at cam dot ac dot uk


--- Comment #85 from jv244 at cam dot ac dot uk  2007-03-16 11:52 ---
(In reply to comment #84)

 Could you post your cpuflags? There should be lahf_lm flag present for
 opterons.
 

flags   : fpu vme de pse tsc msr pae mce cx8 apic sep mtrr pge mca cmov
pat pse36 clflush dts acpi mmx fxsr sse sse2 ss ht tm syscall nx lm
constant_tsc pni monitor ds_cpl vmx est tm2 cx16 xtpr lahf_lm


-- 


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



[Bug fortran/29975] [meta-bugs] ICEs with CP2K

2007-03-16 Thread jv244 at cam dot ac dot uk


--- Comment #86 from jv244 at cam dot ac dot uk  2007-03-16 12:07 ---
(In reply to comment #85)
 (In reply to comment #84)
 
  Could you post your cpuflags? There should be lahf_lm flag present for
  opterons.

sorry, the previous post was of the wrong machine... these are the correct
flags and no (lahf_lm):
cpu family  : 15
model   : 5
model name  : AMD Opteron(tm) Processor 840
stepping: 8
flags   : fpu vme de pse tsc msr pae mce cx8 apic sep mtrr pge mca cmov
pat pse36 clflush mmx fxsr sse sse2 syscall nx mmxext lm 3dnowext 3dnow


-- 


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



[Bug fortran/29975] [meta-bugs] ICEs with CP2K

2007-03-16 Thread jv244 at cam dot ac dot uk


--- Comment #89 from jv244 at cam dot ac dot uk  2007-03-16 14:16 ---
 
 Thanks for your reports!
 

and you for your fixes... things are back to working now.


-- 


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



[Bug tree-optimization/30965] Fails to tree-combine conditions in COND_EXPRs

2007-03-16 Thread jv244 at cam dot ac dot uk


--- Comment #2 from jv244 at cam dot ac dot uk  2007-03-16 19:38 ---
just to keep track, patch here:

http://gcc.gnu.org/ml/gcc-patches/2007-03/msg00129.html


-- 


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



[Bug fortran/29975] [meta-bugs] ICEs with CP2K

2007-03-14 Thread jv244 at cam dot ac dot uk


--- Comment #77 from jv244 at cam dot ac dot uk  2007-03-14 14:48 ---
Currently 

GNU Fortran (GCC) 4.3.0 20070313 (experimental)

there seems to be a new gcc error on CP2K:

gfortran -c -O3 -ftree-loop-linear -ftree-vectorize -ffast-math -march=opteron
-msse2 fparser.f90

/tmp/ccNk6D7G.s: Assembler messages:
/tmp/ccNk6D7G.s:820: Error: suffix or operands invalid for `sahf'
make[2]: *** [fparser.o] Error 1
make[2]: *** Waiting for unfinished jobs
rm fftrot.f90 fftpre.f90 fft_lib.f90 mltfftsg_tools.f90 fftw2_lib.f90
fftacml_lib.f90 fftessl_lib.f90 mltfftsg.f90 ctrig.f90 fftmkl_lib.f90
fftsci_lib.f90 cp2k.f90 fftw3_lib.f90 fftsg_lib.f90 fftstp.f90
make[2]: Leaving directory
`/scratch/vondele/clean/cp2k/obj/Linux-x86-64-gfortran/sopt'
make[1]: *** [build] Error 2


-- 


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



[Bug fortran/29975] [meta-bugs] ICEs with CP2K

2007-03-14 Thread jv244 at cam dot ac dot uk


--- Comment #79 from jv244 at cam dot ac dot uk  2007-03-14 15:14 ---
(In reply to comment #78)

 
 Could you post the temporary asm (only lines around line 820 will be enough) 
 to
 check what is going wrong?
 

.L157:
movslq  %r13d,%rax
imulq   %rsi, %rax
addq%rdx, %rax
movlpd  (%rbx,%rax,8), %xmm2
cvttsd2si   %xmm2, %edi
cvtsi2sd%edi, %xmm1
comisd  %xmm1, %xmm2
jae .L117
decl%edi
cvtsi2sd%edi, %xmm1
.L117:
movsd   %xmm2, (%rsp)
fldl(%rsp)
movsd   %xmm1, (%rsp)
fldl(%rsp)
fxch%st(1)
.L120:
fprem
fnstsw  %ax
sahf
jp  .L120
fstp%st(1)
xorpd   %xmm2, %xmm2
fstpl   24(%rsp)
movlpd  24(%rsp), %xmm1
comisd  %xmm2, %xmm1
jne .L146
call_gfortran_pow_r8_i4
movsd   %xmm0, (%rbx,%r12,8)
jmp .L123
.L146:
xorl%edx, %edx
movl$60, %r8d
movl$5, %ecx
movl$.LC7, %esi
movl$.LC8, %edi
call__termination__stop_program_old
movq32(%rsp), %rax
movq__fparser__comp+8(%rip), %rdx
movq__fparser__comp(%rip), %rbp
movq__fparser__comp+24(%rip), %r15
movl(%rax), %eax
movq%rdx, 8(%rsp)
movl%eax, 20(%rsp)
jmp .L123


-- 


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



[Bug fortran/29975] [meta-bugs] ICEs with CP2K

2007-03-14 Thread jv244 at cam dot ac dot uk


--- Comment #82 from jv244 at cam dot ac dot uk  2007-03-14 16:29 ---
 
 Huh, I somehow misread opteron for athlon. Your code is OK for x86_64, but it
 looks to me that you will have to upgrade binutils.
 

upgrading binutils is not much of an option for me, but with -march=x86-64 I
get the code to compile again. Unfortunately, with the (nice!) option
-march=native, this issue also re-appears. From a user point of view it would
be nice to have gcc detect the version of binutils installed (BTW, the
requirements on the web pages still mention binutils 2.13, which might be
correct for 4.0 but would need updating ?)


-- 


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



[Bug middle-end/30835] ICE with -O2 -ftree-loop-linear

2007-03-14 Thread jv244 at cam dot ac dot uk


--- Comment #3 from jv244 at cam dot ac dot uk  2007-03-14 16:30 ---
(In reply to comment #2)

this issue now seems fixed on trunk for me as well, so I guess this could be
closed.


-- 


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



[Bug tree-optimization/31079] New: 300% difference between ifort/gfortran

2007-03-08 Thread jv244 at cam dot ac dot uk
I'm still trying to find a reduced testcase (or better source) for PR 31021,
but I'm not sure the code below is really the same issue. However, it
illustrates a rather small program with a very significant slowdown in gfortran
relative to ifort.

[EMAIL PROTECTED]:/data/vondele/extracted_collocate/test ifort -O2 -xT test.f90
test.f90(17) : (col. 7) remark: LOOP WAS VECTORIZED.
test.f90(20) : (col. 7) remark: LOOP WAS VECTORIZED.
test.f90(24) : (col. 4) remark: BLOCK WAS VECTORIZED.
[EMAIL PROTECTED]:/data/vondele/extracted_collocate/test ./a.out
   3.544221
[EMAIL PROTECTED]:/data/vondele/extracted_collocate/test gfortran -O3
-march=native -ftree-vectorize  -ffast-math  test.f90
[EMAIL PROTECTED]:/data/vondele/extracted_collocate/test ./a.out
   11.84874
[EMAIL PROTECTED]:/data/vondele/extracted_collocate/test gfortran -O2
-march=native -ftree-vectorize  -ffast-math  test.f90
[EMAIL PROTECTED]:/data/vondele/extracted_collocate/test ./a.out
   11.84474
[EMAIL PROTECTED]:/data/vondele/extracted_collocate/test cat test.f90
SUBROUTINE collocate_core_2_2_0_0(jg,cmax)
IMPLICIT NONE
integer, INTENT(IN)  :: jg,cmax
INTEGER, PARAMETER :: wp = SELECTED_REAL_KIND ( 14, 200 )
INTEGER, PARAMETER :: N=1000
TYPE vec
  real(wp) :: a(2)
END TYPE vec
TYPE(vec) :: dpy(1000)
TYPE(vec) ::  pxy(1000)
real(wp) s(04)
integer :: i

CALL USE(dpy,pxy,s)

DO i=1,N
   pxy(i)%a=0.0_wp
ENDDO
DO i=1,N
   dpy(i)%a=0.0_wp
ENDDO


s(01)=0.0_wp
s(02)=0.0_wp
s(03)=0.0_wp
s(04)=0.0_wp

DO i=1,N
  s(01)=s(01)+pxy(i)%a(1)*dpy(i)%a(1)
  s(02)=s(02)+pxy(i)%a(2)*dpy(i)%a(1)
  s(03)=s(03)+pxy(i)%a(1)*dpy(i)%a(2)
  s(04)=s(04)+pxy(i)%a(2)*dpy(i)%a(2)
ENDDO

CALL USE(dpy,pxy,s)

END SUBROUTINE

SUBROUTINE USE(a,b,c)
 INTEGER, PARAMETER :: wp = SELECTED_REAL_KIND ( 14, 200 )
 REAL(kind=wp) :: a(*),b(*),c(*)
END SUBROUTINE USE

PROGRAM TEST
integer, parameter :: cmax=5
integer*8 :: t1,t2,tbest
real :: time1,time2
jg=0
CALL cpu_time(time1)
tbest=huge(tbest)
DO i=1,100
 ! t1=nanotime_ia32()
   CALL collocate_core_2_2_0_0(0,cmax)
 ! t2=nanotime_ia32()
 ! if(t2-t10 .AND. t2-t1tbest) tbest=t2-t1
ENDDO
CALL cpu_time(time2)
! write(6,*) tbest,time2-time1
write(6,*) time2-time1
END PROGRAM TEST


-- 
   Summary: 300% difference between ifort/gfortran
   Product: gcc
   Version: 4.3.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: tree-optimization
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=31079



[Bug tree-optimization/31079] 300% difference between ifort/gfortran

2007-03-08 Thread jv244 at cam dot ac dot uk


--- Comment #1 from jv244 at cam dot ac dot uk  2007-03-08 11:11 ---
The following is (for me) an even more interesting example, as it times only
the loop that thus the actual multiply / add but also tricks my version of
ifort into generating the expected asm. Ifort is about twice as fast as
gfortran on it.

SUBROUTINE collocate_core_2_2_0_0(jg,cmax)
IMPLICIT NONE
integer, INTENT(IN)  :: jg,cmax
INTEGER, PARAMETER :: wp = SELECTED_REAL_KIND ( 14, 200 )
INTEGER, PARAMETER :: N=10,Nit=1
TYPE vec
  real(wp) :: a(2)
END TYPE vec
TYPE(vec) :: dpy(1000)
TYPE(vec) ::  pxy(1000)
TYPE(vec) :: s(02)
integer :: i,j


DO i=1,N
pxy(i)%a=0.0_wp
ENDDO
DO i=1,N
dpy(i)%a=0.0_wp
ENDDO

s(01)%a(1)=0.0_wp
s(01)%a(2)=0.0_wp
s(02)%a(1)=0.0_wp
s(02)%a(2)=0.0_wp

CALL USE(dpy,pxy,s)

DO j=1,Nit
DO i=1,N
  s(01)%a(:)=s(01)%a(:)+pxy(i)%a(:)*dpy(i)%a(1)
  s(02)%a(:)=s(02)%a(:)+pxy(i)%a(:)*dpy(i)%a(2)
ENDDO
ENDDO

CALL USE(dpy,pxy,s)

END SUBROUTINE

[EMAIL PROTECTED]:/data/vondele/extracted_collocate/test gfortran -O2
-march=native -ftree-vectorize  -ffast-math  test.f90
[EMAIL PROTECTED]:/data/vondele/extracted_collocate/test ./a.out
   4.288268
[EMAIL PROTECTED]:/data/vondele/extracted_collocate/test ifort -O2 -xT test.f90
test.f90(16) : (col. 8) remark: LOOP WAS VECTORIZED.
test.f90(19) : (col. 8) remark: LOOP WAS VECTORIZED.
test.f90(31) : (col. 6) remark: LOOP WAS VECTORIZED.
test.f90(31) : (col. 6) remark: LOOP WAS VECTORIZED.
test.f90(32) : (col. 6) remark: LOOP WAS VECTORIZED.
test.f90(32) : (col. 6) remark: LOOP WAS VECTORIZED.
[EMAIL PROTECTED]:/data/vondele/extracted_collocate/test ./a.out
   1.944121

The inner loop asm looks, with ifort, also the way I was hoping it to look
like:

.B2.7: # Preds ..B2.7 ..B2.6
movddup   -16+collocate_core_2_2_0_0_$DPY.0.0(%rcx), %xmm2 #31.41
movddup   -8+collocate_core_2_2_0_0_$DPY.0.0(%rcx), %xmm3 #32.41
addq  $16, %rdx #33.4
movapdcollocate_core_2_2_0_0_$PXY.0.0(%rdx), %xmm4  #31.6
mulpd %xmm4, %xmm2  #31.39
mulpd %xmm3, %xmm4  #32.39
addpd %xmm2, %xmm1  #31.7
addpd %xmm4, %xmm0  #32.7
addq  $16, %rcx #33.5
cmpq  $160, %rcx#33.4
jle   ..B2.7# Prob 90%  #33.4
# LOE rdx rcx rbx rbp r12 r13 r14 r15 eax xmm0
xmm1


-- 


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



[Bug tree-optimization/31040] New: unroll/peel loops not aggressive enough

2007-03-05 Thread jv244 at cam dot ac dot uk
Looking at the asm for the program below, there plenty of loops left after
compiling with

 gfortran  -S -march=native -O3 -funroll-loops -funroll-all-loops -fpeel-loops 
 test.f90

or any combination of these options. A full unrolling (and in that case a
return of the value 3) would be possible and much faster.

 cat test.f90

INTEGER FUNCTION lxy()
   lxy=0
   DO lxa=0,1
   DO lxb=0,0
 DO lya=0,1-lxa
 DO lyb=0,0-lxb
   lxy=lxy+1
 ENDDO
 ENDDO
   ENDDO
   ENDDO
END FUNCTION
write(6,*) lxy()
END


-- 
   Summary: unroll/peel loops not aggressive enough
   Product: gcc
   Version: 4.3.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: tree-optimization
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=31040



[Bug tree-optimization/31040] unroll/peel loops not aggressive enough

2007-03-05 Thread jv244 at cam dot ac dot uk


--- Comment #2 from jv244 at cam dot ac dot uk  2007-03-05 11:47 ---
(In reply to comment #1)
 We don't unroll non-innermost loops at the moment.  I don't know if sccp can
 be taught to handle this case (and if it's worth it).

such small loops are quite typical for some quantum chemistry integral
routines.
I'm just experimenting rewriting the kernel mentioned in PR 31021. If I do this
unrolling by hand I get quite a speedup on the full kernel:

hand unrolled:
# best time5.260329
loops:
# best time6.616413

which is quite impressive because these loops take at most 30% of the kernel
total time: 

The actual code in question is:

 coef(:,:)=0.0_wp
 lxy=0 ; lx=0
 DO lxa=0,1
 DO lxb=0,1
  lx = lx + 1
  g1=0.0_wp
  g2=0.0_wp
  g1k=0.0_wp
  g2k=0.0_wp
  DO lya=0,1-lxa
  DO lyb=0,1-lxb
lxy=lxy+1
g1=g1+pyx(1,lxy)*dpy(lyb,lya,jg)
g2=g2+pyx(1,lxy)*dpy(lyb,lya,jg2)
g1k=g1k+pyx(2,lxy)*dpy(lyb,lya,jg)
g2k=g2k+pyx(2,lxy)*dpy(lyb,lya,jg2)
  ENDDO
  ENDDO
  DO icoef=1,3
 coef(icoef,1)=coef(icoef,1)+alpha(icoef,lx)*g1
 coef(icoef,2)=coef(icoef,2)+alpha(icoef,lx)*g2
 coef(icoef,3)=coef(icoef,3)+alpha(icoef,lx)*g1k
 coef(icoef,4)=coef(icoef,4)+alpha(icoef,lx)*g2k
  ENDDO
 ENDDO
 ENDDO

and the hand-unrolling just explicitly expands all loops to the loop free
version of exactly the same statements:

 coef(:,:)=0.0_wp
  g1=0.0_wp
  g2=0.0_wp
  g1k=0.0_wp
  g2k=0.0_wp
g1=g1+pyx(1,1)*dpy(0,0,jg)
g2=g2+pyx(1,1)*dpy(0,0,jg2)
g1k=g1k+pyx(2,1)*dpy(0,0,jg)
g2k=g2k+pyx(2,1)*dpy(0,0,jg2)
g1=g1+pyx(1,2)*dpy(1,0,jg)
g2=g2+pyx(1,2)*dpy(1,0,jg2)
g1k=g1k+pyx(2,2)*dpy(1,0,jg)
g2k=g2k+pyx(2,2)*dpy(1,0,jg2)
g1=g1+pyx(1,3)*dpy(0,1,jg)
g2=g2+pyx(1,3)*dpy(0,1,jg2)
g1k=g1k+pyx(2,3)*dpy(0,1,jg)
g2k=g2k+pyx(2,3)*dpy(0,1,jg2)
g1=g1+pyx(1,4)*dpy(1,1,jg)
g2=g2+pyx(1,4)*dpy(1,1,jg2)
g1k=g1k+pyx(2,4)*dpy(1,1,jg)
g2k=g2k+pyx(2,4)*dpy(1,1,jg2)
 coef(01,01)=coef(01,01)+alpha(1,1)*g1
 coef(01,02)=coef(01,02)+alpha(1,1)*g2
 coef(01,03)=coef(01,03)+alpha(1,1)*g1k
 coef(01,04)=coef(01,04)+alpha(1,1)*g2k
 coef(02,01)=coef(02,01)+alpha(2,1)*g1
 coef(02,02)=coef(02,02)+alpha(2,1)*g2
 coef(02,03)=coef(02,03)+alpha(2,1)*g1k
 coef(02,04)=coef(02,04)+alpha(2,1)*g2k
 coef(03,01)=coef(03,01)+alpha(3,1)*g1
 coef(03,02)=coef(03,02)+alpha(3,1)*g2
 coef(03,03)=coef(03,03)+alpha(3,1)*g1k
 coef(03,04)=coef(03,04)+alpha(3,1)*g2k
  g1=0.0_wp
  g2=0.0_wp
  g1k=0.0_wp
  g2k=0.0_wp
g1=g1+pyx(1,5)*dpy(0,0,jg)
g2=g2+pyx(1,5)*dpy(0,0,jg2)
g1k=g1k+pyx(2,5)*dpy(0,0,jg)
g2k=g2k+pyx(2,5)*dpy(0,0,jg2)
g1=g1+pyx(1,6)*dpy(0,1,jg)
g2=g2+pyx(1,6)*dpy(0,1,jg2)
g1k=g1k+pyx(2,6)*dpy(0,1,jg)
g2k=g2k+pyx(2,6)*dpy(0,1,jg2)
 coef(01,01)=coef(01,01)+alpha(1,2)*g1
 coef(01,02)=coef(01,02)+alpha(1,2)*g2
 coef(01,03)=coef(01,03)+alpha(1,2)*g1k
 coef(01,04)=coef(01,04)+alpha(1,2)*g2k
 coef(02,01)=coef(02,01)+alpha(2,2)*g1
 coef(02,02)=coef(02,02)+alpha(2,2)*g2
 coef(02,03)=coef(02,03)+alpha(2,2)*g1k
 coef(02,04)=coef(02,04)+alpha(2,2)*g2k
 coef(03,01)=coef(03,01)+alpha(3,2)*g1
 coef(03,02)=coef(03,02)+alpha(3,2)*g2
 coef(03,03)=coef(03,03)+alpha(3,2)*g1k
 coef(03,04)=coef(03,04)+alpha(3,2)*g2k
  g1=0.0_wp
  g2=0.0_wp
  g1k=0.0_wp
  g2k=0.0_wp
g1=g1+pyx(1,7)*dpy(0,0,jg)
g2=g2+pyx(1,7)*dpy(0,0,jg2)
g1k=g1k+pyx(2,7)*dpy(0,0,jg)
g2k=g2k+pyx(2,7)*dpy(0,0,jg2)
g1=g1+pyx(1,8)*dpy(1,0,jg)
g2=g2+pyx(1,8)*dpy(1,0,jg2)
g1k=g1k+pyx(2,8)*dpy(1,0,jg)
g2k=g2k+pyx(2,8)*dpy(1,0,jg2)
 coef(01,01)=coef(01,01)+alpha(1,3)*g1
 coef(01,02)=coef(01,02)+alpha

[Bug fortran/29975] [meta-bugs] ICEs with CP2K

2007-03-03 Thread jv244 at cam dot ac dot uk


--- Comment #75 from jv244 at cam dot ac dot uk  2007-03-03 10:12 ---
 Joost. I wonder if you have done OpenMP testing, also (I
 imagine that, OpenMP being frequently broken on cp2k and gfortran being a free
 compiler OpenMP-capable, you might have tried it :)

No, haven't tried it yet. So far I have had relatively little interest in
openmp, because the openmp bits in CP2K are really few, and really bad...
mainly because our focus is on massively parallel. However, things are changing
quickly on that front as well, and we'll soon have a 8 cpu x 2 core (AMD)
shared memory machine for experimenting a bit more seriously with this (among
other things). One issue with OpenMP is that it is very easy to break an OpenMP
code (it is just comments), unless you force all developers to always compile
the openmp version as well (or you add one more automatic tester). The other
thing is that some of the mistakes one can make with openmp easily (such as a
forgotten critical section) only trigger bugs from time to time, e.g. depending
on how threads are scheduled. Anyway, many excuses to say 'not really, but
maybe soon'...


-- 


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



[Bug rtl-optimization/31021] New: gfortran 20% slower than ifort on CP2K computational kernel

2007-03-02 Thread jv244 at cam dot ac dot uk
I've extracted the computational kernel of CP2K (see PR 29975) for easier
benchmarking. Together with required utility routines to turn it into a
self-contained program and data to test it, I have made it available here:

http://www.pci.unizh.ch/vandevondele/tmp/extracted_collocate.tgz

the summary is that (yesterday's trunk) gfortran is about 20% slower than ifort
(ifort (IFORT) 9.1 20060707) on my machine. To reproduce, untar the above link,
and use (after specifying the relevant FC in the Makefile)
make
make run

a run takes a few seconds, and yields 
gfortran '-O3 -march=native -ffast-math -ffree-form -ftree-vectorize':
 # of primitives   154502
 # computational kernel timings5
 Kernel time   4.612288
 Kernel time   4.616289
 [...]
ifort  -xP -O3 -free
 # of primitives   154502
 # computational kernel timings5
 Kernel time   3.796237
 Kernel time   3.800237
[...]

which is in this case 21.5% slower. I haven't found any options that made
gfortran much faster (in fact timings are very unsensitive to the options
used), and it is unrelated to any IPO (I actually notice ifort now that is
slightly faster at -O2). Since this might be relevant, timings are on:

vendor_id   : GenuineIntel
cpu family  : 6
model   : 15
model name  : Intel(R) Core(TM)2 CPU  6600  @ 2.40GHz
stepping: 6

The computational time is ~80% due to a single routine (collocate_core in
grid_fast.F), which in turn is dominated by the inner loops in the select case
statement, and of those, the one over ig is (should be) dominant. For example,
the loop starting at line 216 of grid_fast.F. If I look at the asm for this
loop (with my best guess of what that loop might be, I have little experience),
my main observation is that it contains 36 mov* instructions with intel and 51
mov* instructions with gfortran (and the same number of mulsd and addsd), which
could explain the slowdown. I'll attach the respective asm.

I'm of course happy to try other compile flags for gfortran, and also hints on
how to rewrite the kernels in order to get better performance with  gfortran
would be much appreciated.


-- 
   Summary: gfortran 20% slower than ifort on CP2K computational
kernel
   Product: gcc
   Version: 4.3.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: rtl-optimization
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=31021



[Bug rtl-optimization/31021] gfortran 20% slower than ifort on CP2K computational kernel

2007-03-02 Thread jv244 at cam dot ac dot uk


--- Comment #1 from jv244 at cam dot ac dot uk  2007-03-02 08:39 ---
Created an attachment (id=13131)
 -- (http://gcc.gnu.org/bugzilla/attachment.cgi?id=13131action=view)
gfortran kernel asm 


-- 


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



[Bug rtl-optimization/31021] gfortran 20% slower than ifort on CP2K computational kernel

2007-03-02 Thread jv244 at cam dot ac dot uk


--- Comment #2 from jv244 at cam dot ac dot uk  2007-03-02 08:39 ---
Created an attachment (id=13132)
 -- (http://gcc.gnu.org/bugzilla/attachment.cgi?id=13132action=view)
ifort kernel asm


-- 


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



[Bug fortran/29975] [meta-bugs] ICEs with CP2K

2007-03-02 Thread jv244 at cam dot ac dot uk


--- Comment #73 from jv244 at cam dot ac dot uk  2007-03-02 08:41 ---
I've added PR 31021 to track some performance issue with gfortran on one of
CP2K's kernels.


-- 


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



[Bug rtl-optimization/31021] gfortran 20% slower than ifort on CP2K computational kernel

2007-03-02 Thread jv244 at cam dot ac dot uk


--- Comment #4 from jv244 at cam dot ac dot uk  2007-03-02 09:55 ---
(In reply to comment #3)
 On my AMD Athlon(tm) 64 X2 Dual Core Processor 4800+, gfortran is in x86_64
 mode only 13% slower:
 gfortran: Kernel time 5.872366, real 0m33.121s; user 0m32.898s; sys 0m0.088s.
 Ifort:Kernel time 5.244328, real 0m28.893s, user 0m28.758s, sys 0m0.076s.
 Options: ifort -xP -O3 -xW -free and gfortran -O3 -march=native -ffast-math
 -ffree-form -ftree-vectorize -funroll-loops.
 
 For grid_fast.F, one difference is which loops are vectorized; ifort 
 vectorizes
 the loops in line 44, 469, 483 and 496, gfortran only vectorizes the loops in
 line 496 and 469; for the other ones:
 
 grid_fast.F:44: note: not vectorized: complicated access pattern.
   DO lz=1,lz_max(lxy)
  lxyz=lxyz+1
  pyx(1,lxy)=pyx(1,lxy)+pzyx(lxyz)*polz(lxyz,kg)
  pyx(2,lxy)=pyx(2,lxy)+pzyx(lxyz)*polz(lxyz,kg2)
   ENDDO

this might matter a bit, but this is not in an inner loop, so I don't think it
accounts for a lot of time. Having it vectorized would be good of course.

 
 grid_fast.F:483: note: not vectorized: can't determine dependence between
 (*coef_447)[D.1967_2320] and (*coef_447)[D.1967_2320]
   DO icoef=1,coef_max
  coef(icoef,1)=coef(icoef,1)+alpha(icoef,lx)*g1
  coef(icoef,2)=coef(icoef,2)+alpha(icoef,lx)*g2
  coef(icoef,3)=coef(icoef,3)+alpha(icoef,lx)*g1k
  coef(icoef,4)=coef(icoef,4)+alpha(icoef,lx)*g2k
   ENDDO
 

This part, which is in the default part of the switch statement should only be
executed in rare cases. I doubt it matters much in the overall timings. Also,
this loop has very short trips (i.e. coef_max should, for the provided input,
be at most 5).


-- 


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



[Bug rtl-optimization/31021] gfortran 20% slower than ifort on CP2K computational kernel

2007-03-02 Thread jv244 at cam dot ac dot uk


--- Comment #5 from jv244 at cam dot ac dot uk  2007-03-02 18:15 ---
  
  grid_fast.F:483: note: not vectorized: can't determine dependence between
  (*coef_447)[D.1967_2320] and (*coef_447)[D.1967_2320]
DO icoef=1,coef_max
   coef(icoef,1)=coef(icoef,1)+alpha(icoef,lx)*g1
   coef(icoef,2)=coef(icoef,2)+alpha(icoef,lx)*g2
   coef(icoef,3)=coef(icoef,3)+alpha(icoef,lx)*g1k
   coef(icoef,4)=coef(icoef,4)+alpha(icoef,lx)*g2k
ENDDO
  
 
 This part, which is in the default part of the switch statement should only be
 executed in rare cases. I doubt it matters much in the overall timings. Also,
 this loop has very short trips (i.e. coef_max should, for the provided input,
 be at most 5).

I verified that the default branch is indeed not called frequently enough for
this to matter. However, by deleting all other cases (equivalent, but
specialized code), I can time that case, and find:
gfortran: 6.636415
ifort: 5.252329
which means ifort is about 26% faster for the 'case default' branch.


-- 


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



[Bug tree-optimization/31029] New: missed otimization

2007-03-02 Thread jv244 at cam dot ac dot uk
the following is tiny missed optimization, as it fails to link at -O3

read(5,*) igmin
DO ig=igmin,0
   ig2=1-ig
   if (ig.EQ.ig2) CALL link_error()
ENDDO
END

since ig can only have values in the interval [-huge,0], ig2 can only have
values in [1,huge] and so ig can never be equal to ig2. Code similar to this
appears in PR 31021


-- 
   Summary: missed otimization
   Product: gcc
   Version: 4.3.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: tree-optimization
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=31029



[Bug fortran/29975] [meta-bugs] ICEs with CP2K

2007-02-19 Thread jv244 at cam dot ac dot uk


--- Comment #72 from jv244 at cam dot ac dot uk  2007-02-19 19:51 ---
I checked that gfortran yields correct results for the CP2K testsuite with the
options:
-O0 -g -fbounds-check
and
-O3 -ffast-math -funroll-loops -ftree-vectorize -fomit-frame-pointer -msse2
-march=native
I've added the relevant machine_gfortran.F and arch files to the CP2K CVS, to
facilitate gfortran testing with CVS sources.


-- 


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



[Bug fortran/30869] New: incorrect error message for valid code

2007-02-19 Thread jv244 at cam dot ac dot uk
With recent trunk, gfortran incorrectly generates an error for the following
standard code:

INTEGER, POINTER :: i
ALLOCATE(i)
DO i=1,10
ENDDO
DEALLOCATE(i)
END


-- 
   Summary: incorrect error message for valid code
   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=30869



[Bug fortran/30870] New: incorrect error message for valid code

2007-02-19 Thread jv244 at cam dot ac dot uk
With recent trunk, gfortran incorrectly generates an error for the following
standard code:
MODULE TEST
 INTERFACE xx
   MODULE PROCEDURE xx
 END INTERFACE
 public :: xx
CONTAINS
 SUBROUTINE xx(i)
  INTEGER :: I
  I=7
 END SUBROUTINE
END
MODULE TOO
CONTAINS
 SUBROUTINE SUB(xx,I)
  INTERFACE
SUBROUTINE XX(I)
INTEGER :: I
END SUBROUTINE
  END INTERFACE
  CALL XX(I)
 END SUBROUTINE
END MODULE TOO
PROGRAM TT
 USE TEST
 USE TOO
 INTEGER :: I
 CALL SUB(xx,I)
 IF (I.NE.7) CALL ABORT()
END PROGRAM


-- 
   Summary: incorrect error message for valid code
   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=30870



[Bug fortran/30871] New: incorrect error message for valid code

2007-02-19 Thread jv244 at cam dot ac dot uk
With recent trunk, gfortran incorrectly generates an error for the following
standard code:
TYPE data
 CHARACTER(LEN=3) :: A
END TYPE
TYPE(data), DIMENSION(10), TARGET :: Z
CHARACTER(LEN=1), DIMENSION(:), POINTER :: ptr
Z(:)%A=123
ptr=Z(:)%A(2:2)
write(6,*) ptr
END


-- 
   Summary: incorrect error message for valid code
   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=30871



[Bug fortran/30872] New: incorrect error message for valid code

2007-02-19 Thread jv244 at cam dot ac dot uk
With recent trunk, gfortran incorrectly generates an error for the following
standard code:
MODULE MOD1
 IMPLICIT NONE
 INTEGER, PARAMETER :: dp=KIND(0.0D0)
CONTAINS
  SUBROUTINE pw_compose_stripe(weights,in_val,in_val_first,in_val_last,
 out_val,n_el)

REAL(kind=dp), DIMENSION(0:2), 
  INTENT(in) :: weights
INTEGER  :: n_el
REAL(kind=dp), DIMENSION(1:n_el), 
  INTENT(in) :: in_val
REAL(kind=dp), DIMENSION(1:n_el), 
  INTENT(inout)  :: out_val
REAL(kind=dp), INTENT(in):: in_val_last, in_val_first
out_val=in_val
  END SUBROUTINE pw_compose_stripe
  SUBROUTINE pw_nn_compose_r_work(weights,in_val,out_val,bo)
  REAL(kind=dp), DIMENSION(0:2, 0:2, 0:2)  :: weights
  INTEGER, DIMENSION(2, 3) :: bo
  REAL(kind=dp), DIMENSION(bo(1, 1):bo(2, 
   1), bo(1, 2):bo(2, 2), bo(1, 3):bo(2, 
   3)), INTENT(inout) :: out_val
  REAL(kind=dp), DIMENSION(bo(1, 1):bo(2, 
   1), bo(1, 2):bo(2, 2), bo(1, 3):bo(2, 
   3)), INTENT(in):: in_val
  INTEGER :: n_el,i,j
  REAL(kind=dp)   :: in_val_f, in_val_l
  INTEGER, DIMENSION(3)   :: s
  s(1)=bo(2,1)-bo(1,1)+1
  i=1 ; j=1
  CALL pw_compose_stripe(weights=weights(:,i,j),
  in_val=in_val(:,i,j),
  in_val_first=in_val_f,in_val_last=in_val_l,
  out_val=out_val(:,bo(1,2)+i,bo(1,3)+j),n_el=s(1))
  END SUBROUTINE pw_nn_compose_r_work
END MODULE MOD1

USE MOD1
  REAL(kind=dp), DIMENSION(0:2, 0:2, 0:2)  :: weights
  INTEGER, PARAMETER, DIMENSION(2,3) :: bo= 
  RESHAPE((/-1,1,-1,1,-1,1/),(/2,3/))
  REAL(kind=dp), DIMENSION(bo(1, 1):bo(2, 
   1), bo(1, 2):bo(2, 2), bo(1, 3):bo(2, 
   3))  :: out_val,in_val
  in_val=1.0
  out_val=0.0
  CALL pw_nn_compose_r_work(weights,in_val,out_val,bo)
!  write(6,'(10F5.1)') in_val
!  write(6,'(10F5.1)') out_val
END


-- 
   Summary: incorrect error message for valid code
   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=30872



[Bug fortran/30873] New: incorrect error message for valid code

2007-02-19 Thread jv244 at cam dot ac dot uk
With recent trunk, gfortran incorrectly generates an error for the following
standard code:
MODULE M1
CONTAINS
FUNCTION F2(K)
 INTEGER :: F2,K
 F2=E1(K)
END FUNCTION F2
RECURSIVE FUNCTION F1(I)
 INTEGER :: F1,I,E1
 F1=F2(I)
 RETURN
 ENTRY E1(I)
 E1=-I
 RETURN
END FUNCTION F1
END  MODULE M1
USE M1
IF (F1(1).NE.-1) CALL ABORT()
END


-- 
   Summary: incorrect error message for valid code
   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=30873



[Bug fortran/30874] New: incorrect error message for valid code

2007-02-19 Thread jv244 at cam dot ac dot uk
With recent trunk, gfortran incorrectly generates an error for the following
standard code:
program forall_9
  real, dimension (5, 5, 5, 5) :: a, b, c, d

  a (:, :, :, :) = 4
  forall (i = 1:5)
a (i, i, 6 - i, i) = 7
  end forall
  forall (i = 1:5)
a (i, 6 - i, i, i) = 7
  end forall
  forall (i = 1:5)
a (6 - i, i, i, i) = 7
  end forall
  forall (i = 1:5:2)
a (1, 2, 3, i) = 0
  end forall

  b = a
  c = a
  d = a

  forall (i = 1:5, j = 1:5, k = 1:5, any (a (i, j, k, :) .gt. 6))
forall (l = 1:5, any (a (:, :, :, l) .lt. 2))
  a (i, j, k, l) = i - j + k - l + 0.5
end forall
  end forall

  forall (l = 1:5, any (b (:, :, :, l) .lt. 2))
forall (i = 1:5, j = 1:5, k = 1:5, any (b (i, j, k, :) .gt. 6))
  b (i, j, k, l) = i - j + k - l + 0.5
end forall
  end forall

  forall (i = 1:5, j = 1:5, k = 1:5, any (c (i, j, k, :) .gt. 6))
forall (l = 1:5, any (c (:, :, :, l) .lt. 2))
  c (i, j, k, l) = i - j + k - l + 0.5 + c (l, k, j, i)
end forall
  end forall

  forall (l = 1:5, any (d (:, :, :, l) .lt. 2))
forall (i = 1:5, j = 1:5, k = 1:5, any (d (i, j, k, :) .gt. 6))
  d (i, j, k, l) = i - j + k - l + 0.5 + d (l, k, j, i)
end forall
  end forall

  do i = 1, 5
do j = 1, 5
  do k = 1, 5
do l = 1, 5
  r = 4
  if ((i == j .and. k == 6 - i) .or. (i == k .and. j == 6 - i)) then
if (l /= 2 .and. l /= 4) then
  r = 1
elseif (l == i) then
  r = 7
end if
  elseif (j == k .and. i == 6 - j) then
if (l /= 2 .and. l /= 4) then
  r = 1
elseif (l == j) then
  r = 7
end if
  elseif (i == 1 .and. j == 2 .and. k == 3 .and. l /= 2 .and. l /= 4)
then
r = 0
  end if
  s = r
  if (r == 1) then
r = i - j + k - l + 0.5
if (((l == k .and. j == 6 - l) .or. (l == j .and. k == 6 - l))
.and. (i == l)) then
  s = r + 7
elseif (k == j .and. l == 6 - k .and. i == k) then
  s = r + 7
elseif (l /= 1 .or. k /= 2 .or. j /= 3 .or. i == 2 .or. i == 4)
then
  s = r + 4
else
  s = r
end if
  end if
  if (a (i, j, k, l) /= r) call abort ()
  if (c (i, j, k, l) /= s) call abort ()
end do
  end do
end do
  end do

  if (any (a /= b .or. c /= d)) call abort ()
end


-- 
   Summary: incorrect error message for valid code
   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=30874



[Bug fortran/30875] New: incorrect error message for valid code

2007-02-19 Thread jv244 at cam dot ac dot uk
With recent trunk, gfortran incorrectly generates an error for the following
standard code:
TYPE T1
 sequence
 integer :: i=1
END TYPE T1
TYPE T2
 sequence
 integer :: i=1
END TYPE T2
TYPE(T1) :: a1
TYPE(T2) :: a2
EQUIVALENCE(a1,a2)
write(6,*) a1,a2
END


-- 
   Summary: incorrect error message for valid code
   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=30875



[Bug fortran/30876] New: incorrect error message for valid code

2007-02-19 Thread jv244 at cam dot ac dot uk
With recent trunk, gfortran incorrectly generates an error for the following
standard code:
MODULE M1
CONTAINS
 FUNCTION correct_input(i)
   INTEGER :: i,correct_input(5)
   IF (i1) correct_input=test(1)
   IF (i5) correct_input=test(5)
 END FUNCTION correct_input

 RECURSIVE FUNCTION test(i)
  INTEGER :: test(5),i,j
  IF (i1 .OR. i5) THEN
test=correct_input(i)
  ELSE
test=0
test(1:6-i)=(/(j,j=i,5)/)
test=test(3)
  ENDIF
 END FUNCTION

END MODULE M1

USE M1
IF (ANY(TEST(3).NE.(/5,5,5,5,5/))) CALL ABORT()
IF (ANY(TEST(6).NE.(/0,0,0,0,0/))) CALL ABORT()
END


-- 
   Summary: incorrect error message for valid code
   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=30876



[Bug fortran/30877] New: incorrect error message for valid code

2007-02-19 Thread jv244 at cam dot ac dot uk
With recent trunk, gfortran incorrectly generates an error for the following
standard code:
MODULE M1
 INTERFACE OPERATOR(*)
  MODULE PROCEDURE F1
 END INTERFACE
CONTAINS
 FUNCTION F1(a,b) RESULT (c)
  COMPLEX, dimension(2,2), INTENT(IN) :: a
  COMPLEX, dimension(2), INTENT(IN)   :: b
  COMPLEX, dimension(2)   :: c
  c=matmul(a,b)
 END FUNCTION F1
END MODULE M1

USE M1
COMPLEX, dimension(2,2) :: a
COMPLEX, dimension(2)   :: b
COMPLEX, dimension(2)   :: c
a=0 ; b=0
c=a*b
END


-- 
   Summary: incorrect error message for valid code
   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=30877



[Bug fortran/30878] New: incorrect error message for valid code

2007-02-19 Thread jv244 at cam dot ac dot uk
With recent trunk, gfortran incorrectly generates an error for the following
standard code:
 MODULE M1
 CONTAINS
   INTEGER FUNCTION F1()
 NAMELIST /NML/ F1
 F1=1
   END FUNCTION
   INTEGER FUNCTION F2()
 F2=1
   END FUNCTION
 END MODULE
 END


-- 
   Summary: incorrect error message for valid code
   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=30878



[Bug fortran/30879] New: incorrect error message for valid code

2007-02-19 Thread jv244 at cam dot ac dot uk
With recent trunk, gfortran incorrectly generates an error for the following
standard code:
  TYPE T1
   INTEGER :: I
  END TYPE T1
  TYPE(T1), PARAMETER :: D1=T1(2)
  INTEGER :: a(2)
  DATA (a(i),i=1,D1%I) /D1%I*D1%I/
  END


-- 
   Summary: incorrect error message for valid code
   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=30879



[Bug fortran/30880] New: incorrect error message for valid code

2007-02-19 Thread jv244 at cam dot ac dot uk
With recent trunk, gfortran incorrectly generates an error for the following
standard code:
MODULE M1
 TYPE T1
  INTEGER :: i=7
 END TYPE T1
CONTAINS
 FUNCTION F1(d1) RESULT(res)
  INTEGER :: res
  TYPE(T1), INTENT(OUT) :: d1
  TYPE(T1), INTENT(INOUT) :: d2
  res=d1%i
  d1%i=0
  RETURN
  ENTRY   E1(d2) RESULT(res)
  res=d2%i
  d2%i=0
 END FUNCTION F1
END MODULE M1
USE M1
TYPE(T1) :: D1
D1=T1(3)
write(6,*) F1(D1)
D1=T1(3)
write(6,*) E1(D1)
END


-- 
   Summary: incorrect error message for valid code
   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=30880



[Bug fortran/30881] New: incorrect error message for valid code

2007-02-19 Thread jv244 at cam dot ac dot uk
With recent trunk, gfortran incorrectly generates an error for the following
standard code:
INTEGER, PARAMETER :: K=1
INTEGER ::  I
I=TRANSFER(.TRUE.,K)
SELECT CASE(I)
CASE(TRANSFER(.TRUE.,K))
CASE(TRANSFER(.FALSE.,K))
 CALL ABORT()
CASE DEFAULT
 CALL ABORT()
END SELECT
I=TRANSFER(.FALSE.,K)
SELECT CASE(I)
CASE(TRANSFER(.TRUE.,K))
 CALL ABORT()
CASE(TRANSFER(.FALSE.,K))
CASE DEFAULT
 CALL ABORT()
END SELECT
END


-- 
   Summary: incorrect error message for valid code
   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=30881



[Bug fortran/30882] New: incorrect error message for valid code

2007-02-19 Thread jv244 at cam dot ac dot uk
With recent trunk, gfortran incorrectly generates an error for the following
standard code:
SUBROUTINE S1(a)
 INTEGER :: a(*)
 IF(SIZE(a(1:10),1).NE.10) CALL ABORT()
END SUBROUTINE S1
INTEGER :: a(10)
CALL S1(a)
END


-- 
   Summary: incorrect error message for valid code
   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=30882



[Bug fortran/30883] New: incorrect error message for valid code

2007-02-19 Thread jv244 at cam dot ac dot uk
With recent trunk, gfortran incorrectly generates an error for the following
standard code:
MODULE M1
IMPLICIT NONE
CONTAINS
 SUBROUTINE S1(F1)
   INTERFACE
 FUNCTION F1()
 END FUNCTION F1
   END INTERFACE
 END SUBROUTINE S1
END MODULE

END


-- 
   Summary: incorrect error message for valid code
   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=30883



[Bug fortran/29975] [meta-bugs] ICEs with CP2K

2007-02-17 Thread jv244 at cam dot ac dot uk


--- Comment #69 from jv244 at cam dot ac dot uk  2007-02-17 09:17 ---
(In reply to comment #68)
 Current gfortran compiles the code with the standard -OX switches, however,
 still ICEs with '-O2 -fbounds-check -ftree-vectorize -ftree-loop-linear
 -ffast-math -O2 -msse3' on our local opteron.
 
 all_cp2k_gfortran.f90: In function ‘xas_env_init’:
 all_cp2k_gfortran.f90:315153: internal compiler error: Segmentation fault
 

compiling the offending module with 'gfortran -ftree-loop-linear -O2' is enough
to trigger the ICE


-- 


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



[Bug middle-end/30835] New: ICE with -O2 -ftree-loop-linear

2007-02-17 Thread jv244 at cam dot ac dot uk
the following, reduced from PR29975,  causes a gfortran ICE:

MODULE test
  INTEGER, PARAMETER :: dp=KIND(0.0D0), xas_scf_default=1, xas_2s_type=2
  TYPE xas_control_type
INTEGER :: state_type,nexc_atoms
  END TYPE
  TYPE xas_environment_type
INTEGER :: scf_method
  END TYPE
CONTAINS
  SUBROUTINE xas_env_init(xas_env, xas_control)
TYPE(xas_environment_type), POINTER  :: xas_env
TYPE(xas_control_type)   :: xas_control
REAL(dp), DIMENSION(:, :), POINTER   :: sto_alpha

  IF(xas_env%scf_method==xas_scf_default) THEN
ALLOCATE(sto_alpha(1,0:1),STAT=istat)
  ELSEIF( xas_control%state_type == xas_2s_type ) THEN
ALLOCATE(sto_alpha(2,0:1),STAT=istat)
  END IF
  DO iat = 1,xas_control%nexc_atoms
sto_alpha = 0.0_dp
  END DO
  END SUBROUTINE xas_env_init
END MODULE



gfortran -O2 -ftree-loop-linear test.f90
test.f90: In function ‘xas_env_init’:
test.f90:10: internal compiler error: Segmentation fault
Please submit a full bug report,
with preprocessed source if appropriate.
See URL:http://gcc.gnu.org/bugs.html for instructions.


-- 
   Summary: ICE with -O2 -ftree-loop-linear
   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=30835



[Bug fortran/29975] [meta-bugs] ICEs with CP2K

2007-02-17 Thread jv244 at cam dot ac dot uk


--- Comment #71 from jv244 at cam dot ac dot uk  2007-02-17 16:17 ---
(In reply to comment #68)
 Current gfortran compiles the code with the standard -OX switches, however,
 still ICEs with '-O2 -fbounds-check -ftree-vectorize -ftree-loop-linear
 -ffast-math -O2 -msse3' on our local opteron.

This is now PR 30835


-- 


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



[Bug fortran/29975] [meta-bugs] ICEs with CP2K

2007-02-16 Thread jv244 at cam dot ac dot uk


--- Comment #68 from jv244 at cam dot ac dot uk  2007-02-17 07:50 ---
Current gfortran compiles the code with the standard -OX switches, however,
still ICEs with '-O2 -fbounds-check -ftree-vectorize -ftree-loop-linear
-ffast-math -O2 -msse3' on our local opteron.

all_cp2k_gfortran.f90: In function ‘xas_env_init’:
all_cp2k_gfortran.f90:315153: internal compiler error: Segmentation fault


-- 

jv244 at cam dot ac dot uk changed:

   What|Removed |Added

 Status|RESOLVED|REOPENED
 Resolution|FIXED   |


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



[Bug fortran/29975] [meta-bugs] ICEs with CP2K

2007-02-15 Thread jv244 at cam dot ac dot uk


--- Comment #65 from jv244 at cam dot ac dot uk  2007-02-16 05:57 ---
(In reply to comment #64)
 I now have a machine at home here running i686-pc-gnu-linux that I plan to set
 up daily compile test on.  Joost, does that link in coment #63 get updated
 daily?
 

No, the idea is that you want to do the testing on a fixed version of CP2K,
i.e. that it is sure that any failure you might observe is due to a change in
the compiler, and not because we messed up CP2K (which also happens). You'll
certainly get the majority of regressions wrt CP2K this way. I also suggest
that this tarbal is kept available elsewhere, since it is on a tmp part of the
webserver.


-- 


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



[Bug fortran/29975] [meta-bugs] ICEs with CP2K

2007-02-13 Thread jv244 at cam dot ac dot uk


--- Comment #60 from jv244 at cam dot ac dot uk  2007-02-13 09:20 ---
 When you have a moment, could you confirm that all is now well with trunk,
 please? Once again, I am sorry about the breakage.  Now I see Daniel's
 testcase, I realise that I could easily have devised a test... with 20:20
 hindsight:)
Yes, current trunk compiles CP2K again at -O0 (still blocked by PR 30391 at
-O1). No need to apologize, I realize that many of the change you make fall
into the 'subtle' category and do not pop-up with the normal regtesting. As
said before, I'm, unfortunately, used to the fact that even good commercial
compilers (say NAG's f95, IBM's xlf90, Intel's ifort) regress on CP2K from time
to time. It is very annoying to have to fight compilers, after the computer
center upgraded a machine. My hope is that CP2K being freely available (even in
a handy single file format, see initial comment) could prevent this from
happening. Ultimately, I want to see some runtime regression tester... maybe I
should try to get CP2K in a future version of SPEC ... any hints on how to do
that ??


-- 


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



[Bug fortran/29975] [meta-bugs] ICEs with CP2K

2007-02-13 Thread jv244 at cam dot ac dot uk


--- Comment #63 from jv244 at cam dot ac dot uk  2007-02-13 20:04 ---
 Well, I'd add it to my testsuite if weren't a PITA to figure out how to
 make it build.

wget http://www.pci.unizh.ch/vandevondele/tmp/all_cp2k_gfortran.f90.gz
gunzip all_cp2k_gfortran.f90.gz
gfortran -c all_cp2k_gfortran.f90


-- 


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



[Bug fortran/29975] [meta-bugs] ICEs with CP2K

2007-02-12 Thread jv244 at cam dot ac dot uk


--- Comment #48 from jv244 at cam dot ac dot uk  2007-02-12 15:56 ---
Currently, there is a new ICE on CP2K (see initial comment) that happens at any
optimisation level:

 gfortran -c all_cp2k_gfortran.f90
all_cp2k_gfortran.f90:118549: internal compiler error: Segmentation fault
Please submit a full bug report,
with preprocessed source if appropriate.
See URL:http://gcc.gnu.org/bugs.html for instructions.

this is a new regression. I really think CP2K should be added to some nightly
tester somewhere by gfortran developers...


-- 


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



[Bug fortran/29975] [meta-bugs] ICEs with CP2K

2007-02-12 Thread jv244 at cam dot ac dot uk


--- Comment #50 from jv244 at cam dot ac dot uk  2007-02-12 17:09 ---

  I really think CP2K should be added to some nightly
  tester somewhere by gfortran developers...
 
 Well, I second that, but we first need to get it working (like, the middle-end
 people have to move on PR30391).
 
I agree that are two separate issues. One is to get it to work (and keep it
that way), and the other would be to monitor runtime performance. For the
latter issue I can prepare reasonable benchmark inputs, while for the former I
think it is good enough to just compile the tarbal from the initial comment.


-- 


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



[Bug fortran/29975] [meta-bugs] ICEs with CP2K

2007-02-12 Thread jv244 at cam dot ac dot uk


--- Comment #51 from jv244 at cam dot ac dot uk  2007-02-12 17:12 ---

 I'm pretty sure it's the same problem that was already reported here:
 http://gcc.gnu.org/ml/fortran/2007-02/msg00250.html
 
 Of course, a confirmation wouldn't hurt, but I don't have time right now. If
 you manage to confirm this, it'd be nice to send a mail to the list.

The line corresponding to the error messageis:

IF (failure) NULLIFY(sll)


I don't know if this triggers something, looks like a simple statement.


-- 


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



[Bug fortran/29975] [meta-bugs] ICEs with CP2K

2007-02-12 Thread jv244 at cam dot ac dot uk


--- Comment #53 from jv244 at cam dot ac dot uk  2007-02-12 17:52 ---
(In reply to comment #52)
  I don't know if this triggers something, looks like a simple statement.
 
 Yes that triggers my memory of PR 30391.
 

No, that one only happens at -O1 and above, the current ICE is at -O0


-- 


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



[Bug fortran/29975] [meta-bugs] ICEs with CP2K

2007-02-12 Thread jv244 at cam dot ac dot uk


--- Comment #55 from jv244 at cam dot ac dot uk  2007-02-12 18:26 ---

 Nonetheless, I do not see it being associated with my doo-doo in module.c, do
 you?

I'm not an expert, but this is a traceback, leading to module.c:
Program received signal SIGSEGV, Segmentation fault.
gfc_insert_bbt (root=0x0, new=0x7a23c80, compare=0x459ed0 compare_symtree)
at /scratch/vondele/gcc_trunk/gcc/gcc/fortran/bbt.c:137
137   *r = insert (n, *r, compare);
(gdb) bt
#0  gfc_insert_bbt (root=0x0, new=0x7a23c80, compare=0x459ed0
compare_symtree)
at /scratch/vondele/gcc_trunk/gcc/gcc/fortran/bbt.c:137
#1  0x00459d34 in gfc_new_symtree (root=0x0, name=0x7fbfffe980
@20233)
at /scratch/vondele/gcc_trunk/gcc/gcc/fortran/symbol.c:1909
#2  0x0043a44a in get_unique_symtree (ns=0x0)
at /scratch/vondele/gcc_trunk/gcc/gcc/fortran/module.c:1775
#3  0x0043ca1a in read_cleanup (p=0x7c7f9f0)
at /scratch/vondele/gcc_trunk/gcc/gcc/fortran/module.c:3290
#4  0x0043c9db in read_cleanup (p=0x7922d50)
at /scratch/vondele/gcc_trunk/gcc/gcc/fortran/module.c:3284
#5  0x0043c9db in read_cleanup (p=0x7a26300)
at /scratch/vondele/gcc_trunk/gcc/gcc/fortran/module.c:3284
#6  0x0043c9db in read_cleanup (p=0x7c77ec0)
at /scratch/vondele/gcc_trunk/gcc/gcc/fortran/module.c:3284
#7  0x0043c9db in read_cleanup (p=0x79dfbf0)
at /scratch/vondele/gcc_trunk/gcc/gcc/fortran/module.c:3284
#8  0x0043c9db in read_cleanup (p=0x7af9f20)
at /scratch/vondele/gcc_trunk/gcc/gcc/fortran/module.c:3284
#9  0x0043c9db in read_cleanup (p=0x7af2390)
at /scratch/vondele/gcc_trunk/gcc/gcc/fortran/module.c:3284
#10 0x0043d10d in read_module () at
/scratch/vondele/gcc_trunk/gcc/gcc/fortran/module.c:3563
#11 0x0043d555 in gfc_use_module () at
/scratch/vondele/gcc_trunk/gcc/gcc/fortran/module.c:4164
#12 0x00442b98 in accept_statement (st=Variable st is not available.
) at /scratch/vondele/gcc_trunk/gcc/gcc/fortran/parse.c:1255
#13 0x00443625 in parse_spec (st=ST_USE) at
/scratch/vondele/gcc_trunk/gcc/gcc/fortran/parse.c:1887
#14 0x00444e9a in gfc_parse_file () at
/scratch/vondele/gcc_trunk/gcc/gcc/fortran/parse.c:3063
#15 0x004631ae in gfc_be_parse_file (set_yydebug=Variable set_yydebug
is not available.


-- 


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



[Bug fortran/30779] New: incomplete file triggers ICE

2007-02-12 Thread jv244 at cam dot ac dot uk
trying to find a testcase for what is currently an issue in PR29975 I ran into
this:

[EMAIL PROTECTED]:/scratch/vondele/clean/cp2k/obj/Linux-x86-64-gfortran/sdbg
gfortran t.f90
t.f90:0: internal compiler error: Segmentation fault
Please submit a full bug report,
with preprocessed source if appropriate.
See URL:http://gcc.gnu.org/bugs.html for instructions.
[EMAIL PROTECTED]:/scratch/vondele/clean/cp2k/obj/Linux-x86-64-gfortran/sdbg
cat t.f90
MODULE M1
 INTEGER :: I
END MODULE M1

USE M1,ONLY: I,


-- 
   Summary: incomplete file triggers ICE
   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=30779



[Bug fortran/29975] [meta-bugs] ICEs with CP2K

2007-02-12 Thread jv244 at cam dot ac dot uk


--- Comment #57 from jv244 at cam dot ac dot uk  2007-02-12 19:18 ---

 Yes, that's the one: http://gcc.gnu.org/ml/fortran/2007-02/msg00250.html
 

for people reducing the bug, I found that it is in the module cp_fm_pool_types.
This indicates the the line number indicated in the segfault would be wrong.
Trying to reduce the testcase further, my automatic script got stuck on what is
now PR 30779


-- 


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



[Bug fortran/30779] incomplete file triggers ICE

2007-02-12 Thread jv244 at cam dot ac dot uk


--- Comment #2 from jv244 at cam dot ac dot uk  2007-02-12 20:12 ---
(In reply to comment #1)
 Confirmed.
 
 Backtrace:
 
 (gdb) r t.f90
 Starting program: /home/ig25/libexec/gcc/i686-pc-linux-gnu/4.3.0/f951 t.f90
 Failed to read a valid object file image from memory.
 t.f90:1:
 
 cat t.f90
 1
 Error: Unclassifiable statement at (1)
 
 Program received signal SIGSEGV, Segmentation fault.
 0x0809a6d7 in gfc_next_char_literal (in_string=0)
 at /home/ig25/gcc/trunk/gcc/fortran/scanner.c:711
 711   if (gfc_current_locus.lb-linenum == continue_line + 1)
 
looks like you discovered an independent bug, in my case the 'cat t.f90' wasn't
part of the program (but it is the command line that wraps) and in my case
there is no error message.


-- 


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



[Bug libfortran/15516] assembly snippets for nano second resolution wall clock time

2007-02-11 Thread jv244 at cam dot ac dot uk


--- Comment #2 from jv244 at cam dot ac dot uk  2007-02-11 10:55 ---
(In reply to comment #0)
 If you extract the object
 file get_clockfreq.o from /usr/lib/librt.a then you can call the function
 __get_clockfreq() to determine clock frequency. To extract the routine, try:
 
 ar xv /usr/lib/librt.a get_clockfreq.o
 
 To use the routines as timers, you can use the following routine. Call it 
 before
 and after the section of code you want to time and the difference will be the
 elapsed time. Be sure to include the appropriate routine from above.

is this comment about get_clockfreq.o actually correct ? I find it returns
different values depending on the load of the machine (I guess this is
frequency rescaling at work, i.e.):

 46799775 159600 0.029323167293233084
 46703250 159600 0.029262687969924813
 40773807 159600 0.02554749812030075
 34589439 239400 0.014448387218045113
 33201315 159600 0.020802828947368422
 34758144 239400 0.014518857142857142
 33325110 159600 0.020880394736842105
 34576236 239400 0.014442872180451127

where the first number is the ticks as returned by differences of
nanotime_ia32, and the second the number returned by get_clockfreq, the third
is the estimated time if seconds (quite random, since it is allways the same
matrix multiply). (an unrelated issue is that it wraps pretty quicky...)


-- 


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



[Bug middle-end/30391] [4.3 regression] ICE at -O1 with conditional expressions and GIMPLE_MODIFY_STMT

2007-02-05 Thread jv244 at cam dot ac dot uk


--- Comment #6 from jv244 at cam dot ac dot uk  2007-02-05 20:12 ---
a patch:

http://gcc.gnu.org/ml/gcc-patches/2007-02/msg00353.html


-- 


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



[Bug target/30484] Miscompilation of remainder expressions on CPUs of the i386 family

2007-01-16 Thread jv244 at cam dot ac dot uk


--- Comment #5 from jv244 at cam dot ac dot uk  2007-01-17 07:14 ---
(In reply to comment #0)
 The program below shows (at all the optimization levels) a miscompilation of
 the remainder expression that causes INT_MIN % -1 to cause a SIGFPE on CPUs of
 the i386 family.

notice that this is language dependent. I.e. in Fortran the equivalent of the
above 'INT_MIN % -1' is undefined. So, whatever the fix for C and friends, it
should not slow down Fortran programs using MOD.


-- 


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



[Bug fortran/29975] [meta-bugs] ICEs with CP2K

2007-01-05 Thread jv244 at cam dot ac dot uk


--- Comment #44 from jv244 at cam dot ac dot uk  2007-01-06 06:30 ---
Current gcc ICEs again on CP2K:



gfortran -c -O3 -ftree-vectorize -ffast-math -march=opteron -fopenmp
mc_coordinates.f90
mc_coordinates.f90: In function ‘check_for_overlap’:
mc_coordinates.f90:192: internal compiler error: in operand_equal_p, at
fold-const.c:2539
Please submit a full bug report,
with preprocessed source if appropriate.
See URL:http://gcc.gnu.org/bugs.html for instructions.


-- 

jv244 at cam dot ac dot uk changed:

   What|Removed |Added

 Status|RESOLVED|REOPENED
 Resolution|FIXED   |


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



[Bug fortran/29975] [meta-bugs] [4.1 and 4.2 only] ICEs with CP2K

2006-12-19 Thread jv244 at cam dot ac dot uk


--- Comment #40 from jv244 at cam dot ac dot uk  2006-12-19 12:49 ---
I've now checked that gcc trunk (revision 120045) compiles CP2K (at -O3
-ftree-vectorize -ffast-math -march=opteron) and that the numerical results
seem acceptable. Great job... I hope the the original file is kept around so
that gfortran doesn't regress on this.

I've also checked the fortran-experiments branch to see how it performs on
CP2K's libint_interface.f90 (as preprocessed with -D__LIBINT), but it looks
like gfortran's  ISO_C_BINDING stuff is not yet ready. That file might be a
nice testcase as well (compiles with g95, but unfortunately fails on the
versions of xlf90 and NAG I have access to, because of unimplemented features)


-- 


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



[Bug fortran/29975] [meta-bugs] [4.1 and 4.2 only] ICEs with CP2K

2006-12-13 Thread jv244 at cam dot ac dot uk


--- Comment #37 from jv244 at cam dot ac dot uk  2006-12-13 14:01 ---
(In reply to comment #36)

well, this was reduced, filed as PR30147, and fixed. Tobias reduced another one
and filed it as PR30190 (see dependencies).


-- 


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



[Bug fortran/30200] New: valgrind errors for write statement

2006-12-13 Thread jv244 at cam dot ac dot uk
[EMAIL PROTECTED]:/scratch/vondele/clean/cp2k/tests/QS/regtest-gpw-2 gfortran
test.f90
[EMAIL PROTECTED]:/scratch/vondele/clean/cp2k/tests/QS/regtest-gpw-2 ./a.out
 [EMAIL PROTECTED]:/scratch/vondele/clean/cp2k/tests/QS/regtest-gpw-2 valgrind
--tool=memcheck ./a.out
==16188== Memcheck, a memory error detector.
==16188== Copyright (C) 2002-2005, and GNU GPL'd, by Julian Seward et al.
==16188== Using LibVEX rev 1575, a library for dynamic binary translation.
==16188== Copyright (C) 2004-2005, and GNU GPL'd, by OpenWorks LLP.
==16188== Using valgrind-3.1.1, a dynamic binary instrumentation framework.
==16188== Copyright (C) 2000-2005, and GNU GPL'd, by Julian Seward et al.
==16188== For more details, rerun with: -v
==16188==
==16188== Invalid read of size 1
==16188==at 0x4B93D8D: formatted_transfer_scalar (transfer.c:834)
==16188==by 0x4B94182: formatted_transfer (transfer.c:1355)
==16188==by 0x400CF2: MAIN__ (in
/scratch/vondele/clean/cp2k/tests/QS/regtest-gpw-2/a.out)
==16188==by 0x400D2D: main (fmain.c:18)
==16188==  Address 0x5148646 is 6 bytes inside a block of size 10 free'd
==16188==at 0x4A1984D: free (vg_replace_malloc.c:235)
==16188==by 0x400CC6: MAIN__ (in
/scratch/vondele/clean/cp2k/tests/QS/regtest-gpw-2/a.out)
==16188==by 0x400D2D: main (fmain.c:18)
==16188==
==16188== Invalid read of size 1
==16188==at 0x4B93DA9: formatted_transfer_scalar (transfer.c:838)
==16188==by 0x4B94182: formatted_transfer (transfer.c:1355)
==16188==by 0x400CF2: MAIN__ (in
/scratch/vondele/clean/cp2k/tests/QS/regtest-gpw-2/a.out)
==16188==by 0x400D2D: main (fmain.c:18)
==16188==  Address 0x5148647 is 7 bytes inside a block of size 10 free'd
==16188==at 0x4A1984D: free (vg_replace_malloc.c:235)
==16188==by 0x400CC6: MAIN__ (in
/scratch/vondele/clean/cp2k/tests/QS/regtest-gpw-2/a.out)
==16188==by 0x400D2D: main (fmain.c:18)
 a ==16188==
==16188== ERROR SUMMARY: 2 errors from 2 contexts (suppressed: 3 from 2)
==16188== malloc/free: in use at exit: 0 bytes in 0 blocks.
==16188== malloc/free: 11 allocs, 11 frees, 29,400 bytes allocated.
==16188== For counts of detected errors, rerun with: -v
==16188== All heap blocks were freed -- no leaks are possible.
[EMAIL PROTECTED]:/scratch/vondele/clean/cp2k/tests/QS/regtest-gpw-2 cat
test.f90
   character(len=100) myfmt
   type test
character(len=100) :: names(5)
   end type test
   type(test) :: keyword
   keyword%names=(/a,b,c,d,e/)
   myfmt=1X
   WRITE(unit=6,fmt=(//TRIM(myfmt)//,a,' '),advance=NO)
TRIM(keyword%names(1))
   END


-- 
   Summary: valgrind errors for write statement
   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=30200



[Bug fortran/29975] [meta-bugs] [4.1 and 4.2 only] ICEs with CP2K

2006-12-13 Thread jv244 at cam dot ac dot uk


--- Comment #39 from jv244 at cam dot ac dot uk  2006-12-13 15:25 ---
I had a look at one of the failing testcases from CP2K testsuite, and under
valgrind there were a number of errors that could be reproduced in the small
testcase of PR30200


-- 


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



[Bug fortran/30200] valgrind errors for write statement

2006-12-13 Thread jv244 at cam dot ac dot uk


--- Comment #1 from jv244 at cam dot ac dot uk  2006-12-13 19:28 ---
This problem seems to be at the root of most CP2K regtest failures described in
PR29975


-- 


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



[Bug libfortran/30200] write(*,myfmt=(1X,a,'xyz')) A prints Az' instead of Axyz

2006-12-13 Thread jv244 at cam dot ac dot uk


--- Comment #7 from jv244 at cam dot ac dot uk  2006-12-14 06:41 ---
(In reply to comment #6)
 More information.  I get Tobias bad result with -m64 on x86-64-Linux.  The
 problem goes away with -m32.
 
 $ gfortran -m32 pr30200-2.f90 
 $ ./a.out
  Axyz
 $ gfortran -m64 pr30200-2.f90 
 $ ./a.out
  Az'

whereas -m32 is printing the right result, I think it is coincidence, at least
to original testcase still yields valgrind errors at runtime if compiled with
-m32


-- 


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



[Bug fortran/29975] [meta-bugs] [4.1 and 4.2 only] ICEs with CP2K

2006-12-11 Thread jv244 at cam dot ac dot uk


--- Comment #30 from jv244 at cam dot ac dot uk  2006-12-11 09:51 ---
(In reply to comment #29)

simple testcase for the segfault:

SUBROUTINE S(unit_number)
character(len=100) :: status_string
integer :: unit_number,istat
status_string=KEEP
CLOSE (UNIT=unit_number,IOSTAT=istat,STATUS=TRIM(status_string))
END SUBROUTINE

INTEGER :: unit_number
unit_number=100
OPEN(unit_number)
CALL S(unit_number)
END


-- 


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



[Bug fortran/29975] [meta-bugs] [4.1 and 4.2 only] ICEs with CP2K

2006-12-11 Thread jv244 at cam dot ac dot uk


--- Comment #32 from jv244 at cam dot ac dot uk  2006-12-11 11:29 ---
(In reply to comment #31)
   gcc version 4.3.0 20061210 (experimental)
  simple testcase for the segfault:
 I tried it with gfortran 4.3 and 4.2 (today's build) and an older 4.1 build 
 and
 neither crashes. valgrind also shows no error.


OK, latest svn and a build from scratch resolved that segfault. Could there be
something wrong with the gcc build system ?


-- 


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



[Bug fortran/29975] [meta-bugs] [4.1 and 4.2 only] ICEs with CP2K

2006-12-11 Thread jv244 at cam dot ac dot uk


--- Comment #33 from jv244 at cam dot ac dot uk  2006-12-11 11:54 ---
Running the CP2K regtests now results in:
number of FAILED  tests 24
(these are just the runs that do not complete, I have not checked that the runs
that finish also generate the right numbers. This can be reproduced using the 
do_regtest script mentioned in the initial description). Just for future
reference the current failures are:

 1 
/scratch/vondele/clean/TEST-Linux-x86-64-gfortran-sdbg-2006-12-11T12:27:29+0100/QS/regtest-gpw-2/H2-vib.inp.out
 2 
/scratch/vondele/clean/TEST-Linux-x86-64-gfortran-sdbg-2006-12-11T12:27:29+0100/QS/regtest-gpw-2/H2O-meta_res1.inp.out
 3 
/scratch/vondele/clean/TEST-Linux-x86-64-gfortran-sdbg-2006-12-11T12:27:29+0100/QS/regtest-gpw-2/H2O-meta_res2.inp.out
 4 
/scratch/vondele/clean/TEST-Linux-x86-64-gfortran-sdbg-2006-12-11T12:27:29+0100/QS/regtest-gpw-2/H2O-meta_res3.inp.out
 5 
/scratch/vondele/clean/TEST-Linux-x86-64-gfortran-sdbg-2006-12-11T12:27:29+0100/QS/regtest-gpw-3/H2O-langevin-2.inp.out
 6 
/scratch/vondele/clean/TEST-Linux-x86-64-gfortran-sdbg-2006-12-11T12:27:29+0100/Fist/regtest/water_1_res_3.inp.out
 7 
/scratch/vondele/clean/TEST-Linux-x86-64-gfortran-sdbg-2006-12-11T12:27:29+0100/Fist/regtest/H2O-32_SPME_res_4.inp.out
 8 
/scratch/vondele/clean/TEST-Linux-x86-64-gfortran-sdbg-2006-12-11T12:27:29+0100/Fist/regtest/H2O-32_NPT_res_2.inp.out
 9 
/scratch/vondele/clean/TEST-Linux-x86-64-gfortran-sdbg-2006-12-11T12:27:29+0100/Fist/regtest/H2O-32_NPT_res_3.inp.out
10 
/scratch/vondele/clean/TEST-Linux-x86-64-gfortran-sdbg-2006-12-11T12:27:29+0100/Fist/regtest/H2O-32_NPT_res_4.inp.out
11 
/scratch/vondele/clean/TEST-Linux-x86-64-gfortran-sdbg-2006-12-11T12:27:29+0100/Fist/regtest/silicon_cluster_3.inp.out
12 
/scratch/vondele/clean/TEST-Linux-x86-64-gfortran-sdbg-2006-12-11T12:27:29+0100/Fist/regtest/silicon_cluster_4.inp.out
13 
/scratch/vondele/clean/TEST-Linux-x86-64-gfortran-sdbg-2006-12-11T12:27:29+0100/Fist/regtest/silicon_cluster_5.inp.out
14 
/scratch/vondele/clean/TEST-Linux-x86-64-gfortran-sdbg-2006-12-11T12:27:29+0100/Fist/regtest/silicon_cluster_6.inp.out
15 
/scratch/vondele/clean/TEST-Linux-x86-64-gfortran-sdbg-2006-12-11T12:27:29+0100/QS/regtest-ot-1/H2O-OT-ASPC-6.inp.out
16 
/scratch/vondele/clean/TEST-Linux-x86-64-gfortran-sdbg-2006-12-11T12:27:29+0100/QMMM/QS/regtest-3/C4H10-qmmm-gauss-7.inp.out
17 
/scratch/vondele/clean/TEST-Linux-x86-64-gfortran-sdbg-2006-12-11T12:27:29+0100/Fist/regtest/wat_freq.inp.out
18 
/scratch/vondele/clean/TEST-Linux-x86-64-gfortran-sdbg-2006-12-11T12:27:29+0100/Fist/regtest/wat_freq_norot.inp.out
19 
/scratch/vondele/clean/TEST-Linux-x86-64-gfortran-sdbg-2006-12-11T12:27:29+0100/Fist/regtest/wat_freq_freeze.inp.out
20 
/scratch/vondele/clean/TEST-Linux-x86-64-gfortran-sdbg-2006-12-11T12:27:29+0100/QMMM/QS/regtest-3/C4H10-qmmm-grid-8.inp.out
21 
/scratch/vondele/clean/TEST-Linux-x86-64-gfortran-sdbg-2006-12-11T12:27:29+0100/EP/Ar-ep.inp.out
22 
/scratch/vondele/clean/TEST-Linux-x86-64-gfortran-sdbg-2006-12-11T12:27:29+0100/EP/Ar2.inp.out
23 
/scratch/vondele/clean/TEST-Linux-x86-64-gfortran-sdbg-2006-12-11T12:27:29+0100/EP/3H2O-ep.inp.out
24 
/scratch/vondele/clean/TEST-Linux-x86-64-gfortran-sdbg-2006-12-11T12:27:29+0100/Pimd/h2o_pint.inp.out


Some of them seem to be caused by the same issue, but there is a number of
distinct problems.


-- 


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



[Bug fortran/29975] [meta-bugs] [4.1 and 4.2 only] ICEs with CP2K

2006-12-11 Thread jv244 at cam dot ac dot uk


--- Comment #35 from jv244 at cam dot ac dot uk  2006-12-11 16:08 ---
(In reply to comment #34)
 CP2k actually gives here an ICE with -O2 (PR 30147)
 at least when I use ./do_regtest (otherwise I didn't saw it). I did not yet
 look at why the calculation results are wrong.
 

yes, I'm currently also getting this

gfortran -c -O3 -ftree-vectorize -ffast-math -march=opteron
input_cp2k_motion.f90
input_cp2k_motion.f90: In function ‘create_neb_section’:
input_cp2k_motion.f90:3122: internal compiler error: in fold_convert, at
fold-const.c:2150

in fact, this is on a file added to the CP2K CVS repo 2 days ago, so it is not
yet part of the gzip'ed file that I provided for the initial report. That one
compiles OK at -O2. 


-- 


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



[Bug fortran/29975] [meta-bugs] ICEs with CP2K

2006-12-02 Thread jv244 at cam dot ac dot uk


--- Comment #12 from jv244 at cam dot ac dot uk  2006-12-02 13:37 ---

 I am not sure that I see how the test case in #6 can ever have worked; if it 
 is
 indeed representative of the code in CP2K, I do not see how that can have
 worked either.  

fparser is a relatively new addition to CP2K, so FX statement might be wrt to
an older version of CP2K. I'm not sure that I can completely agree with FX,
I've never seen a gfortran compiled CP2K pass all our regtests without a
segfault. Of course, CP2K is fairly complex so there could be bugs, but it is
also quite wel tested.


-- 


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



[Bug fortran/29975] [meta-bugs] ICEs with CP2K

2006-12-02 Thread jv244 at cam dot ac dot uk


--- Comment #13 from jv244 at cam dot ac dot uk  2006-12-02 13:55 ---
(In reply to comment #11)
 Created an attachment (id=12724)
 -- (http://gcc.gnu.org/bugzilla/attachment.cgi?id=12724action=view) [edit]
 test case for interface bl_copy

 all_cp2k_gfortran.f90:418697.22:
   USE f77_blas_generic
  1
 Error: Name 'bl_copy' at (1) is an ambiguous reference to 'bl_copy' from
 current program unit
 This is an error (see attachment) since the 'bl_copy' is only enhanced by the
 second interface bl_copy (happily accepted by ifort, g95 and NAG f95). 

I don't think this is an error... you can add further compilers to the list of
'believers' xlf90 / pgf90.

 
 And g95 (after using VIRT=3GB of memory for 7m [on a 2GB system]):
 virtual memory exhausted: Cannot allocate memory
 

compiles fine here. However, that's why I'm hoping that the gfortran crew adds
this somewhere to a nightly tester. A whole list of commercial compilers failed
(in the past years) to compile even single files with either memory explosions
/ infinite loops / ICEs ... this is particularly true if things like IPO are
switched on.

first things first however ...


-- 


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



[Bug fortran/29975] [meta-bugs] ICEs with CP2K

2006-12-02 Thread jv244 at cam dot ac dot uk


--- Comment #14 from jv244 at cam dot ac dot uk  2006-12-02 14:00 ---

 Are you in a position to try the patch on CP2K?

no quite so easy right now, but I'll be svn updating as soon as it is in. Looks
like tobias anyway tested it OK.

 your PRs have given me something absorbing 

... there are still a few left, as I find time (likely not before next year)
I'll try to add a few more. My personal experience with this is that they can
be a bit too absorbing.


-- 


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



[Bug fortran/29975] [meta-bugs] ICEs with CP2K

2006-11-29 Thread jv244 at cam dot ac dot uk


--- Comment #8 from jv244 at cam dot ac dot uk  2006-11-29 22:26 ---
(In reply to comment #7)
 Joost,
 
 Do you happen to know at what revision things went bad?
I'm afraid I don't...


-- 


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



[Bug fortran/29975] [meta-bugs] ICEs with CP2K

2006-11-28 Thread jv244 at cam dot ac dot uk


--- Comment #5 from jv244 at cam dot ac dot uk  2006-11-28 15:36 ---
after the fix for 29976 I get with current mainline :

all_cp2k_gfortran.f90:347635: internal compiler error: Segmentation fault
Please submit a full bug report,
with preprocessed source if appropriate.
See URL:http://gcc.gnu.org/bugs.html for instructions.

which is also different from the bugs mentioned in comment 2


-- 


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



[Bug fortran/25620] Missed optimization with power

2006-11-27 Thread jv244 at cam dot ac dot uk


--- Comment #16 from jv244 at cam dot ac dot uk  2006-11-27 16:49 ---
(In reply to comment #15)
 Fixed (partly) on the mainline.  We can now expand pow (x, n/2) and pow (x,
 n/3)
 properly using sqrt and/or cbrt, but cbrt is not available from the fortran
 frontend (it misses to define __builtin_cbrt).
 
Thanks Richard, for this patch, and your other efforts to improve performance
for number crunching applications... 
hopefully the fortran frontend will be fixed as well.


-- 


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



[Bug fortran/29975] New: [metabug] ICEs with CP2K

2006-11-25 Thread jv244 at cam dot ac dot uk
I'm trying to compile CP2K with gfortran (yesterday's mainline), but I'm
experiencing ICEs. Since it seems to be happening more often with CP2K I've
added this metabug.

the first one I see is:

gfortran -c all_cp2k_gfortran.f90
all_cp2k_gfortran.f90: In function âpw_sumupâ:
all_cp2k_gfortran.f90:128714: internal compiler error: in build_int_cst_wide,
at tree.c:852
Please submit a full bug report,
with preprocessed source if appropriate.
See URL:http://gcc.gnu.org/bugs.html for instructions.

the file is to large to be attached in bugzilla, but I've made it available
(temporarily) for download:

http://www.pci.unizh.ch/vandevondele/tmp/all_cp2k_gfortran.f90.gz

it might be a good idea to add it to some gfortran testsuite. People that
prefer more managable sources can get it from
http://cp2k.berlios.de/download.html
plus instructions on how to run the CP2K testsuite (all tests should pass with
gfortran, http://cp2k.berlios.de/regtest.html).


-- 
   Summary: [metabug] ICEs with CP2K
   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=29975



[Bug fortran/29975] [meta] ICEs with CP2K

2006-11-25 Thread jv244 at cam dot ac dot uk


--- Comment #2 from jv244 at cam dot ac dot uk  2006-11-25 14:15 ---
(In reply to comment #1)
 Hi Joost,
 I'll look into it. I now regularly build cp2k with gfortran (usually 4.2
 branch) on i686-linux for my work but I haven't see this ICE yet. Just in 
 case,
 what's the platform you're building on?

x86_64-linux. However, I seem to see ICEs that look more like frontend problems
as well, so I don't think it is all platform dependent. Some see to be in files
that have been recently added, e.g.:

gfortran -c -O3 -ftree-vectorize -ffast-math -march=nocona fparser.f90
fparser.f90:0: internal compiler error: Segmentation fault
Please submit a full bug report,
with preprocessed source if appropriate.
See URL:http://gcc.gnu.org/bugs.html for instructions.

or a bogus error:

f77_blas.f90:22.22:

  USE f77_blas_generic
 1
Error: Name 'bl_copy' at (1) is an ambiguous reference to 'bl_copy' from
current program unit

(the last two I get compiling the 'normal' sources)


-- 

jv244 at cam dot ac dot uk changed:

   What|Removed |Added

  BugsThisDependsOn|29976   |


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



[Bug fortran/25620] Missed optimization with power

2006-09-04 Thread jv244 at cam dot ac dot uk


--- Comment #9 from jv244 at cam dot ac dot uk  2006-09-04 14:10 ---
(In reply to comment #7)
 Looking at how we deal with all this, we seem to like pow() very much during
 folding, even doing the reverse transformations you suggest.  The
 transformation
 back to sqrt ( x**N ) with N being an integer could be done by
 expand_builtin_pow
 in case that computation of sqrt is cheap.  Other than that, exposing integer
 powers is only a win if theres some CSE possibility.

Despite this PR being a bit old, I'd like to add another (similar example, also
from real code) where other compilers generate much better code:

subroutine t(x)
 x=x**1.5
end subroutine t

pgf90:
# lineno: 0
sqrtss  (%rdi), %xmm0
mulss   (%rdi), %xmm0
movss   %xmm0, (%rdi)

gfortran -S -O3 -ffast-math:
movss   (%rdi), %xmm0
movq%rdi, %rbx
movss   .LC0(%rip), %xmm1
callpowf
movss   %xmm0, (%rbx)
popq%rbx
ret

trying to time this with the following fragment:
y=0.
DO i=1,1000
 x=i
 y=y+x**1.5
ENDDO
write(6,*) y
END

pgf90 is about 10 times faster than gfortran


-- 


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



[Bug web/12821] dead link on onlinedocs/gccint/Top-Level.html

2006-06-12 Thread jv244 at cam dot ac dot uk


--- Comment #3 from jv244 at cam dot ac dot uk  2006-06-12 07:18 ---
(In reply to comment #0)

still failing ... since it has been opened about 2.5y ago, should it be closed
as wontfix ?


-- 


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



<    5   6   7   8   9   10   11   12   >