2007-11-18 Thomas Koenig <tkoenig@gcc.gnu.org>
PR fortran/32770
* gfortran.fortran-torture/execute/equiv_5.f: Set kind on
integers so tests works with -fdefault-integer-8.
* gfortran.fortran-torture/execute/elemental.f90: Use default
integers so test passes with -fdefault-integer-8.
* gfortran.fortran-torture/execute/der_io.f90: Increase
buffer length so test passes with -fdefault-integer-8.
* gfortran.dg/bounds_check_8.f90: Likewise.
* gfortran.dg/arrayio_derived_1.f90: LIkewise.
* gfortran.dg/equiv_7.f90: Set kind so test passes
with -fdefault-integer-8.
* gfortran.dg/g77/
20030326-1.f: Set kind explicitly to
provoke overflow.
From-SVN: r130279
+2007-11-18 Thomas Koenig <tkoenig@gcc.gnu.org>
+
+ PR fortran/32770
+ * gfortran.fortran-torture/execute/equiv_5.f: Set kind on
+ integers so tests works with -fdefault-integer-8.
+ * gfortran.fortran-torture/execute/elemental.f90: Use default
+ integers so test passes with -fdefault-integer-8.
+ * gfortran.fortran-torture/execute/der_io.f90: Increase
+ buffer length so test passes with -fdefault-integer-8.
+ * gfortran.dg/bounds_check_8.f90: Likewise.
+ * gfortran.dg/arrayio_derived_1.f90: LIkewise.
+ * gfortran.dg/equiv_7.f90: Set kind so test passes
+ with -fdefault-integer-8.
+ * gfortran.dg/g77/20030326-1.f: Set kind explicitly to
+ provoke overflow.
+
2007-11-18 Jerry DeLisle <jvdelisle@gcc.gnu.org>
PR fortran/33317
character(len=1) :: c
end type tp
type(tp) :: x(5)
- character(len=100) :: a
+ character(len=500) :: a
integer :: i, b(5)
x%i = 256
integer :: x
end type xyz_type
type (xyz_type), dimension(3) :: xyz
- character(len=20) :: s
+ character(len=80) :: s
xyz(1)%x = 11111
xyz(2)%x = 0
function d1mach_little(i) result(d1mach)
implicit none
double precision d1mach,dmach(5)
- integer i,large(4),small(4)
+ integer i
+ integer*4 large(4),small(4)
equivalence ( dmach(1), small(1) )
equivalence ( dmach(2), large(1) )
data small(1),small(2) / 0, 1048576/
function d1mach_big(i) result(d1mach)
implicit none
double precision d1mach,dmach(5)
- integer i,large(4),small(4)
+ integer i
+ integer*4 large(4),small(4)
equivalence ( dmach(1), small(1) )
equivalence ( dmach(2), large(1) )
data small(1),small(2) /1048576, 0/
! For gfortran, see PR 13490
!
integer c
- c = -2147483648 / (-1) ! { dg-error "too big for its kind" "" }
+ c = -2147483648_4 / (-1) ! { dg-error "too big for its kind" "" }
end
! Program to test IO of derived types
program derived_io
- character(100) :: buf1, buf2, buf3
+ character(400) :: buf1, buf2, buf3
type xyz_type
integer :: x
! Program to test elemental functions.
program test_elemental
implicit none
- integer(kind = 4), dimension (2, 4) :: a
- integer(kind = 4), dimension (2, 4) :: b
+ integer, dimension (2, 4) :: a
+ integer, dimension (2, 4) :: b
integer(kind = 8), dimension(2) :: c
a = reshape ((/2, 3, 4, 5, 6, 7, 8, 9/), (/2, 4/))
if (any (a .ne. 0)) call abort
contains
-elemental integer function e_fn (p, q)
+elemental integer(kind=4) function e_fn (p, q)
integer, intent(in) :: p, q
e_fn = p - q
end function
C The testcase is from blas, http://www.netlib.org/blas/d1mach.f
DOUBLE PRECISION FUNCTION D1MACH(I)
- INTEGER I
+ INTEGER*4 I
C
C DOUBLE-PRECISION MACHINE CONSTANTS
C D1MACH( 1) = B**(EMIN-1), THE SMALLEST POSITIVE MAGNITUDE.
C D1MACH( 4) = B**(1-T), THE LARGEST RELATIVE SPACING.
C D1MACH( 5) = LOG10(B)
C
- INTEGER SMALL(2)
- INTEGER LARGE(2)
- INTEGER RIGHT(2)
- INTEGER DIVER(2)
- INTEGER LOG10(2)
- INTEGER SC, CRAY1(38), J
+ INTEGER*4 SMALL(2)
+ INTEGER*4 LARGE(2)
+ INTEGER*4 RIGHT(2)
+ INTEGER*4 DIVER(2)
+ INTEGER*4 LOG10(2)
+ INTEGER*4 SC, CRAY1(38), J
COMMON /D9MACH/ CRAY1
SAVE SMALL, LARGE, RIGHT, DIVER, LOG10, SC
DOUBLE PRECISION DMACH(5)
C DATA LOG10(1),LOG10(2) / O776464202324, O117571775714 /, SC/987/
C
C MACHINE CONSTANTS FOR PDP-11 FORTRANS SUPPORTING
-C 32-BIT INTEGERS.
+C 32-BIT INTEGER*4S.
C DATA SMALL(1),SMALL(2) / 8388608, 0 /
C DATA LARGE(1),LARGE(2) / 2147483647, -1 /
C DATA RIGHT(1),RIGHT(2) / 612368384, 0 /
END
SUBROUTINE I1MCRY(A, A1, B, C, D)
**** SPECIAL COMPUTATION FOR OLD CRAY MACHINES ****
- INTEGER A, A1, B, C, D
+ INTEGER*4 A, A1, B, C, D
A1 = 16777216*B + C
A = 16777216*A1 + D
END