equiv_1.f90: Replace tab(s) with spaces.
2006-03-06 Steven G. Kargl <kargls@comcast.net> * gfortran.dg/equiv_1.f90: Replace tab(s) with spaces. * gfortran.dg/arrayio_1.f90: Ditto. * gfortran.dg/pr25603.f: Ditto. * gfortran.dg/assumed_dummy_2.f90: Ditto. * gfortran.dg/equiv_2.f90: Ditto. * gfortran.dg/arrayio_2.f90: Ditto. * gfortran.dg/namelist_14.f90: Ditto. * gfortran.dg/g77/cpp6.f: Ditto. * gfortran.dg/g77/cpp5inc.h: Ditto. * gfortran.dg/g77/cpp5.F: Ditto. * gfortran.dg/g77/cpp5.h: Ditto. * gfortran.dg/namelist_15.f90: Ditto. * gfortran.dg/badline.f: Ditto. * gfortran.dg/sibling_dummy_procedure_1.f90: Ditto. * gfortran.dg/sibling_dummy_procedure_2.f90: Ditto. * gfortran.dg/backspace_6.f: Ditto. * gfortran.dg/altreturn_1.f90: Ditto. * gfortran.dg/entry_4.f90: Ditto. * gfortran.dg/implicit_5.f90: Ditto. From-SVN: r111790
This commit is contained in:
parent
e3dfd6d555
commit
8ffe548822
20 changed files with 97 additions and 75 deletions
|
@ -1,3 +1,25 @@
|
|||
2006-03-06 Steven G. Kargl <kargls@comcast.net>
|
||||
|
||||
* gfortran.dg/equiv_1.f90: Replace tab(s) with spaces.
|
||||
* gfortran.dg/arrayio_1.f90: Ditto.
|
||||
* gfortran.dg/pr25603.f: Ditto.
|
||||
* gfortran.dg/assumed_dummy_2.f90: Ditto.
|
||||
* gfortran.dg/equiv_2.f90: Ditto.
|
||||
* gfortran.dg/arrayio_2.f90: Ditto.
|
||||
* gfortran.dg/namelist_14.f90: Ditto.
|
||||
* gfortran.dg/g77/cpp6.f: Ditto.
|
||||
* gfortran.dg/g77/cpp5inc.h: Ditto.
|
||||
* gfortran.dg/g77/cpp5.F: Ditto.
|
||||
* gfortran.dg/g77/cpp5.h: Ditto.
|
||||
* gfortran.dg/namelist_15.f90: Ditto.
|
||||
* gfortran.dg/badline.f: Ditto.
|
||||
* gfortran.dg/sibling_dummy_procedure_1.f90: Ditto.
|
||||
* gfortran.dg/sibling_dummy_procedure_2.f90: Ditto.
|
||||
* gfortran.dg/backspace_6.f: Ditto.
|
||||
* gfortran.dg/altreturn_1.f90: Ditto.
|
||||
* gfortran.dg/entry_4.f90: Ditto.
|
||||
* gfortran.dg/implicit_5.f90: Ditto.
|
||||
|
||||
2006-03-06 Volker Reichelt <reichelt@igpm.rwth-aachen.de>
|
||||
|
||||
PR c++/15759
|
||||
|
|
|
@ -1,7 +1,7 @@
|
|||
! { dg-do compile }
|
||||
subroutine foo (a)
|
||||
real t, a, baz
|
||||
call bar (*10)
|
||||
t = 2 * baz ()
|
||||
IF (t.gt.0) t = baz ()
|
||||
10 END
|
||||
subroutine foo (a)
|
||||
real t, a, baz
|
||||
call bar (*10)
|
||||
t = 2 * baz ()
|
||||
IF (t.gt.0) t = baz ()
|
||||
10 END
|
||||
|
|
|
@ -14,11 +14,11 @@
|
|||
read(r,'(3(2x,i4/)/3(3x,i6/))') i
|
||||
if (any(i.ne.(/(j,j=1,6)/))) call abort()
|
||||
do j=1,12
|
||||
do k=1,2
|
||||
if ((j.gt.8.and.k.eq.1).or.(k.eq.2)) then
|
||||
if (r(j,k).ne.'0123456789AB') call abort()
|
||||
end if
|
||||
end do
|
||||
do k=1,2
|
||||
if ((j.gt.8.and.k.eq.1).or.(k.eq.2)) then
|
||||
if (r(j,k).ne.'0123456789AB') call abort()
|
||||
end if
|
||||
end do
|
||||
end do
|
||||
|
||||
! Write to a portion of a character array
|
||||
|
|
|
@ -17,12 +17,12 @@
|
|||
write(r((i-1):(i+1),i), f)
|
||||
|
||||
if ( r(1,1).ne.'hello ' .or. &
|
||||
r(2,1).ne.'world ' .or. &
|
||||
r(3,1).ne.'0123456789ab' .or. &
|
||||
r(4,1).ne.'0123456789ab' .or. &
|
||||
r(1,2).ne.'HELLO ! ' .or. &
|
||||
r(2,2).ne.'WORLD ' .or. &
|
||||
r(3,2).ne.'0123456789ab' .or. &
|
||||
r(4,2).ne.'0123456789ab') call abort()
|
||||
r(2,1).ne.'world ' .or. &
|
||||
r(3,1).ne.'0123456789ab' .or. &
|
||||
r(4,1).ne.'0123456789ab' .or. &
|
||||
r(1,2).ne.'HELLO ! ' .or. &
|
||||
r(2,2).ne.'WORLD ' .or. &
|
||||
r(3,2).ne.'0123456789ab' .or. &
|
||||
r(4,2).ne.'0123456789ab') call abort()
|
||||
|
||||
end program arrayio_2
|
||||
|
|
|
@ -9,7 +9,7 @@ contains
|
|||
end subroutine foo
|
||||
subroutine bar (arr)
|
||||
double precision :: arr(5,*)
|
||||
call foo (arr) ! { dg-error "cannot be an assumed-size array" }
|
||||
call foo (arr) ! { dg-error "cannot be an assumed-size array" }
|
||||
call foo (arr (:, :8))
|
||||
end subroutine
|
||||
end
|
||||
|
|
|
@ -27,7 +27,7 @@
|
|||
backspace 11
|
||||
read(11,end= 1004 )idata
|
||||
if(idata(1).ne.-2 .or.idata(datasize).ne.-3) call abort()
|
||||
stop
|
||||
stop
|
||||
1004 continue
|
||||
end
|
||||
|
||||
|
||||
|
|
|
@ -1,4 +1,4 @@
|
|||
subroutine foo
|
||||
subroutine foo
|
||||
# 18 "src/badline.F" 2
|
||||
end
|
||||
end
|
||||
! { dg-warning "left but not entered" "" { target *-*-* } 2 }
|
||||
|
|
|
@ -1,5 +1,5 @@
|
|||
! { dg-do compile { target i?86-*-* x86_64-*-* } }
|
||||
function f1 () result (r) ! { dg-error "can't be a POINTER" }
|
||||
function f1 () result (r) ! { dg-error "can't be a POINTER" }
|
||||
integer, pointer :: r
|
||||
real e1
|
||||
allocate (r)
|
||||
|
@ -11,14 +11,14 @@ entry e1a ()
|
|||
e1a = 13
|
||||
end function
|
||||
function f2 ()
|
||||
integer, dimension (2, 7, 6) :: e2 ! { dg-error "can't be an array" }
|
||||
integer, dimension (2, 7, 6) :: e2 ! { dg-error "can't be an array" }
|
||||
f2 = 6
|
||||
return
|
||||
entry e2 ()
|
||||
e2 (:, :, :) = 2
|
||||
end function
|
||||
integer(kind=8) function f3 () ! { dg-error "can't be of type" }
|
||||
complex(kind=8) e3 ! { dg-error "can't be of type" }
|
||||
integer(kind=8) function f3 () ! { dg-error "can't be of type" }
|
||||
complex(kind=8) e3 ! { dg-error "can't be of type" }
|
||||
f3 = 1
|
||||
return
|
||||
entry e3 ()
|
||||
|
|
|
@ -1,9 +1,9 @@
|
|||
program broken_equiv
|
||||
real d (2) ! { dg-error "Inconsistent equivalence rules" "d" }
|
||||
real e ! { dg-error "Inconsistent equivalence rules" "e" }
|
||||
real d (2) ! { dg-error "Inconsistent equivalence rules" "d" }
|
||||
real e ! { dg-error "Inconsistent equivalence rules" "e" }
|
||||
equivalence (d (1), e), (d (2), e)
|
||||
|
||||
real f (2) ! { dg-error "Inconsistent equivalence rules" "f" }
|
||||
real f (2) ! { dg-error "Inconsistent equivalence rules" "f" }
|
||||
double precision g (2) ! { dg-error "Inconsistent equivalence rules" "g" }
|
||||
equivalence (f (1), g (1)), (f (2), g (2)) ! Not standard conforming
|
||||
end
|
||||
|
|
|
@ -1,17 +1,17 @@
|
|||
subroutine broken_equiv1
|
||||
character*4 h
|
||||
character*3 i
|
||||
equivalence (h(1:3), i(2:1)) ! { dg-error "has length zero" }
|
||||
equivalence (h(1:3), i(2:1)) ! { dg-error "has length zero" }
|
||||
end subroutine
|
||||
|
||||
subroutine broken_equiv2
|
||||
character*4 j
|
||||
character*2 k
|
||||
equivalence (j(2:3), k(1:5)) ! { dg-error "out of bounds" }
|
||||
equivalence (j(2:3), k(1:5)) ! { dg-error "out of bounds" }
|
||||
end subroutine
|
||||
|
||||
subroutine broken_equiv3
|
||||
character*4 l
|
||||
character*2 m
|
||||
equivalence (l(2:3:4), m(1:2)) ! { dg-error "\[Ss\]yntax error" }
|
||||
equivalence (l(2:3:4), m(1:2)) ! { dg-error "\[Ss\]yntax error" }
|
||||
end subroutine
|
||||
|
|
|
@ -1,4 +1,4 @@
|
|||
! { dg-do run }
|
||||
! { dg-do run }
|
||||
#include "cpp5.h"
|
||||
IF (FOO().NE.1) CALL ABORT ()
|
||||
END
|
||||
IF (FOO().NE.1) CALL ABORT ()
|
||||
END
|
||||
|
|
|
@ -1,3 +1,3 @@
|
|||
FUNCTION FOO()
|
||||
FUNCTION FOO()
|
||||
#include "cpp5inc.h"
|
||||
END FUNCTION
|
||||
END FUNCTION
|
||||
|
|
|
@ -1 +1 @@
|
|||
FOO = 1
|
||||
FOO = 1
|
||||
|
|
|
@ -2,7 +2,7 @@
|
|||
# 1 "<built-in>"
|
||||
# 1 "<command line>"
|
||||
# 1 "test.F"
|
||||
! { dg-do compile }
|
||||
! { dg-do compile }
|
||||
|
||||
# 1 "A234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890" 1
|
||||
|
||||
|
@ -11,10 +11,10 @@
|
|||
# 1 "C234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890" 1
|
||||
|
||||
# 1 "D234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890" 1
|
||||
PARAMETER (I=1)
|
||||
PARAMETER (I=1)
|
||||
|
||||
# 2 "C234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890" 2
|
||||
# 2 "B234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890" 2
|
||||
# 2 "A234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890" 2
|
||||
# 3 "test.F" 2
|
||||
END
|
||||
END
|
||||
|
|
|
@ -1,22 +1,22 @@
|
|||
! PR fortran/21729
|
||||
! { dg-do compile }
|
||||
function f1 () ! { dg-error "has no IMPLICIT type" "f1" }
|
||||
implicit none
|
||||
function f1 () ! { dg-error "has no IMPLICIT type" "f1" }
|
||||
implicit none
|
||||
end function f1
|
||||
function f2 () result (r2) ! { dg-error "has no IMPLICIT type" "r2" }
|
||||
implicit none
|
||||
implicit none
|
||||
end function f2
|
||||
function f3 () ! { dg-error "has no IMPLICIT type" "f3" }
|
||||
implicit none
|
||||
entry e3 () ! { dg-error "has no IMPLICIT type" "e3" }
|
||||
function f3 () ! { dg-error "has no IMPLICIT type" "f3" }
|
||||
implicit none
|
||||
entry e3 () ! { dg-error "has no IMPLICIT type" "e3" }
|
||||
end function f3
|
||||
function f4 ()
|
||||
implicit none
|
||||
real f4
|
||||
entry e4 () ! { dg-error "has no IMPLICIT type" "e4" }
|
||||
implicit none
|
||||
real f4
|
||||
entry e4 () ! { dg-error "has no IMPLICIT type" "e4" }
|
||||
end function f4
|
||||
function f5 () ! { dg-error "has no IMPLICIT type" "f5" }
|
||||
implicit none
|
||||
function f5 () ! { dg-error "has no IMPLICIT type" "f5" }
|
||||
implicit none
|
||||
entry e5 ()
|
||||
real e5
|
||||
real e5
|
||||
end function f5
|
||||
|
|
|
@ -77,18 +77,18 @@ contains
|
|||
close (10)
|
||||
|
||||
if (.not.(dttest (dt(1), mt ((/99,999,9999,99999/))) .and. &
|
||||
dttest (dt(2), mt ((/99,999,9999,99999/))) .and. &
|
||||
dttest (dtl(1), mt ((/41, 42, 43, 44/))) .and. &
|
||||
dttest (dtl(2), mt ((/41, 42, 43, 44/))) .and. &
|
||||
dttest (dts, mt ((/1, 2, 3, 4/))) .and. &
|
||||
dttest (cdt, mt ((/-99,-999,-9999,-99999/))) .and. &
|
||||
all (j ==(/21, 21/)) .and. &
|
||||
all (i ==(/101, 201/)) .and. &
|
||||
(pi == 3.14159_8) .and. &
|
||||
(chs == "singleton") .and. &
|
||||
(chl == "abcdefg") .and. &
|
||||
(cha(1)(1:10) == "first ") .and. &
|
||||
(cha(2)(1:10) == "second "))) call abort ()
|
||||
dttest (dt(2), mt ((/99,999,9999,99999/))) .and. &
|
||||
dttest (dtl(1), mt ((/41, 42, 43, 44/))) .and. &
|
||||
dttest (dtl(2), mt ((/41, 42, 43, 44/))) .and. &
|
||||
dttest (dts, mt ((/1, 2, 3, 4/))) .and. &
|
||||
dttest (cdt, mt ((/-99,-999,-9999,-99999/))) .and. &
|
||||
all (j ==(/21, 21/)) .and. &
|
||||
all (i ==(/101, 201/)) .and. &
|
||||
(pi == 3.14159_8) .and. &
|
||||
(chs == "singleton") .and. &
|
||||
(chl == "abcdefg") .and. &
|
||||
(cha(1)(1:10) == "first ") .and. &
|
||||
(cha(2)(1:10) == "second "))) call abort ()
|
||||
|
||||
end subroutine foo
|
||||
end program namelist_14
|
||||
|
|
|
@ -46,14 +46,14 @@ program namelist_15
|
|||
if (.not. ((x(1)%i(1) == 3) .and. &
|
||||
(x(1)%i(2) == 4) .and. &
|
||||
(x(1)%m(1)%ch(1) == "dz") .and. &
|
||||
(x(1)%m(1)%ch(2) == "ez") .and. &
|
||||
(x(1)%m(1)%ch(2) == "ez") .and. &
|
||||
(x(1)%m(2)%ch(1) == "fz") .and. &
|
||||
(x(1)%m(2)%ch(2) == "gz") .and. &
|
||||
(x(1)%m(2)%ch(2) == "gz") .and. &
|
||||
(x(2)%i(1) == -3) .and. &
|
||||
(x(2)%i(2) == -4) .and. &
|
||||
(x(2)%m(1)%ch(1) == "hz") .and. &
|
||||
(x(2)%m(1)%ch(2) == "qz") .and. &
|
||||
(x(2)%m(1)%ch(2) == "qz") .and. &
|
||||
(x(2)%m(2)%ch(1) == "wz") .and. &
|
||||
(x(2)%m(2)%ch(2) == "kz"))) call abort ()
|
||||
(x(2)%m(2)%ch(2) == "kz"))) call abort ()
|
||||
|
||||
end program namelist_15
|
||||
|
|
|
@ -41,7 +41,7 @@ C
|
|||
DIMENSION WORK(*)
|
||||
|
||||
if (XSTART .NE. 201.0) then
|
||||
call abort
|
||||
call abort
|
||||
endif
|
||||
|
||||
CALL BAR2(NX,NY,NZ,NT,NTIME,NWINDX,NWINDY,NSINKS,NFILT,XSTART,
|
||||
|
|
|
@ -15,7 +15,7 @@ contains
|
|||
subroutine bar(self, z)
|
||||
interface
|
||||
function self(z) result(res)
|
||||
real z
|
||||
real z
|
||||
real(kind=kind(1.0d0)) :: res
|
||||
end function
|
||||
end interface
|
||||
|
@ -23,7 +23,7 @@ contains
|
|||
subroutine xxx(self,z)
|
||||
interface
|
||||
function self(z) result(res)
|
||||
real z
|
||||
real z
|
||||
real(kind=kind(1.0d0)) :: res
|
||||
end function
|
||||
end interface
|
||||
|
|
|
@ -15,7 +15,7 @@ contains
|
|||
subroutine bar(self, z)
|
||||
interface
|
||||
function self(z) result(res)
|
||||
real z
|
||||
real z
|
||||
real(kind=kind(1.0d0)) :: res
|
||||
end function
|
||||
end interface
|
||||
|
@ -23,7 +23,7 @@ contains
|
|||
subroutine xxx(self,z)
|
||||
interface
|
||||
function self(z) result(res)
|
||||
real z
|
||||
real z
|
||||
real(kind=kind(1.0d0)) :: res
|
||||
end function
|
||||
end interface
|
||||
|
|
Loading…
Add table
Reference in a new issue