INTEGER :: b ! { dg-error "Unexpected data declaration statement" }
END ASSOCIATE
END PROGRAM main ! { dg-error "Expecting END ASSOCIATE" }
-! { dg-excess-errors "Unexpected end of file" }
+! { dg-error "Unexpected end of file" "" { target "*-*-*" } 0 }
use A
use B ! { dg-error "Cannot open module file" }
end module C
-! { dg-excess-errors "compilation terminated" }
+! { dg-prune-output "compilation terminated" }
myname2: BLOCK
END BLOCK ! { dg-error "Expected block name of 'myname2'" }
END PROGRAM main ! { dg-error "Expecting END BLOCK" }
-! { dg-excess-errors "Unexpected end of file" }
+! { dg-error "Unexpected end of file" "" { target "*-*-*" } 0 }
program p
type t
character(*), allocatable :: x(*) ! { dg-error "must have a deferred shape" }
- end type
+ end type ! { dg-error "needs to be a constant specification" "" { target "*-*-*" } .-1 }
end
-! { dg-excess-errors "needs to be a constant specification" }
program p
type t
character(*) :: x y ! { dg-error "error in data declaration" }
- end type
+ end type ! { dg-error "needs to be a constant specification" "" { target "*-*-*" } .-1 }
end
-! { dg-excess-errors "needs to be a constant specification" }
program p
type t
character(*) :: x+1 ! { dg-error "error in data declaration" }
- end type
+ end type ! { dg-error "needs to be a constant specification" "" { target "*-*-*" } .-1 }
end
-! { dg-excess-errors "needs to be a constant specification" }
type t
character(2), allocatable :: a(*) ! { dg-error "must have a deferred shape" }
character(*), allocatable :: b(2) ! { dg-error "must have a deferred shape" }
+ ! { dg-error "needs to be a constant specification" "" { target "*-*-*" } .-1 }
character(*), allocatable :: c(*) ! { dg-error "must have a deferred shape" }
- end type
+ end type ! { dg-error "needs to be a constant specification" "" { target "*-*-*" } .-1 }
end
-! { dg-excess-errors "needs to be a constant specification" }
end critical ! "Expecting END PROGRAM statement" (but error above is fatal)
end
-! { dg-excess-errors "compilation terminated" }
+! { dg-prune-output "compilation terminated" }
integer :: val
call co_max(val) ! { dg-error "Coarrays disabled at .1., use '-fcoarray=' to enable" }
end program test
-! { dg-excess-errors "compilation terminated" }
+! { dg-prune-output "compilation terminated" }
data e(2) / 2 / ! { dg-error "re-initialization" }
integer :: f(3) = 0 ! { dg-error "already is initialized" }
- data f(2) / 1 /
+ data f(2) / 1 / ! { dg-error "already is initialized" }
! full array initializer, re-initialize subsection
integer :: g(3)
data g(1:2) / 2*2 / ! { dg-error "re-initialization" }
integer :: h(3) = 1 ! { dg-error "already is initialized" }
- data h(2:3) / 2*2 /
+ data h(2:3) / 2*2 / ! { dg-error "already is initialized" }
! full array initializer, re-initialize full array
integer :: i(3)
data i / 2,2,2 / ! { dg-error "re-initialization" }
integer :: j(3) = 1 ! { dg-error "already is initialized" }
- data j / 3*2 /
+ data j / 3*2 / ! { dg-error "already is initialized" }
END SUBROUTINE
SUBROUTINE data_init_matrix_invalid()
data e(2,3) / 2 / ! { dg-error "re-initialization" }
integer :: f(3,3) = 1 ! { dg-error "already is initialized" }
- data f(3,2) / 2 /
+ data f(3,2) / 2 / ! { dg-error "already is initialized" }
! full array initializer, re-initialize subsection
integer :: g(3,3)
data g(2:3,2:3) / 2, 2*3, 4 / ! { dg-error "re-initialization" }
integer :: h(3,3) = 1 ! { dg-error "already is initialized" }
- data h(2:3,2:3) / 2, 2*3, 4 /
+ data h(2:3,2:3) / 2, 2*3, 4 / ! { dg-error "already is initialized" }
! full array initializer, re-initialize full array
integer :: i(3,3)
data i / 9 * 1 / ! { dg-error "re-initialization" }
integer :: j(3,3) = 0 ! { dg-error "already is initialized" }
- data j / 9 * 1 /
+ data j / 9 * 1 / ! { dg-error "already is initialized" }
END SUBROUTINE
SUBROUTINE data_init_misc_invalid()
! index out-of-bounds, direct access
integer :: b(3)
data b(-2) / 1 / ! { dg-error "below array lower bound" }
-
+ ! { dg-warning "is out of bounds" "" { target *-*-* } .-1 }
! index out-of-bounds, implied do-loop (PR32315)
integer :: i
character(len=20), dimension(4) :: string
data (string(i), i = 1, 5) / 'A', 'B', 'C', 'D', 'E' / ! { dg-error "above array upper bound" }
END SUBROUTINE
-
-! { dg-excess-errors "" }
if(i.eq.5)then
goto 10
10 endif ! { dg-error "is within another block" }
- end
-! { dg-excess-errors "" }
+ end ! { dg-error "END DO statement expected" }
+ ! { dg-warning "Fortran 2018 deleted feature: DO termination statement which is not END DO or CONTINUE" "" { target "*-*-*" } 6 }
+! { dg-error "Unexpected end of file" "" { target "*-*-*" } 0 }
PARAMETER (PLT$B_OPC=0) ! Unreachable as the error above is now fatal
common /abc$def/ PLT$C_HOUSTPIX, PLT$C_COMMAND ! Unreachable as the error above is now fatal
end
-! { dg-excess-errors "compilation terminated" }
+! { dg-prune-output "compilation terminated" }
COMMON RADE3155V62$JUTMU9L9E(3,3,3), LADE314JUTMP9 ! { dg-error "Invalid character '\\$' at .1.. Use '-fdollar-ok' to allow it as an extension" }
+LHEDDJNTMP9L(3,3,3)
end
-! { dg-excess-errors "compilation terminated" }
+! { dg-prune-output "compilation terminated" }
write (*, 10)
! There is a tab character before 'bug!'. This is accepted without
! the -Wno-tabs option or a -std= option.
- 10 format ('Hello ', 'bug!') ! { dg-warning "tab character in format" }
-
+ 10 format ('Hello ', 'bug!') ! { dg-warning "tab character in format at " }
+ ! { dg-warning "tab character at " "" { target "*-*-*" } .-1 }
end
-! { dg-excess-errors "tab character in format" }
program TestFormat
write (*, 10)
10 format ('Hello ', 'bug!') ! { dg-warning "tab character in format" }
- end
-! { dg-excess-errors "tab character in FORMAT" }
+ end ! { dg-warning "tab character at " "" { target "*-*-*" } .-1 }
implicit none
integer i,dest(10)
forall (i=2:ix) dest(i)=i ! { dg-error "has no IMPLICIT type" }
-end
-
-! { dg-excess-errors "Can't convert UNKNOWN to INTEGER" }
+end ! { dg-error "Cannot convert UNKNOWN to INTEGER" "" { target "*-*-*" } .-1 }
c { dg-do compile }
c
-c Following line added on transfer to gfortran testsuite
-c { dg-excess-errors "" }
+c { dg-additional-options "-w" }
c
C JCB comments:
C g77 doesn't accept the added line "integer(kind=7) ..." --
print *, max4
print *, i4, %loc(i4)
print *, i8, %loc(i8)
- call foo(i4, %loc(i4), i8, %loc(i8))
+ call foo(i4, %loc(i4), i8, %loc(i8)) ! { dg-error "Type mismatch in argument 'i8a' at .1.; passed INTEGER.8. to INTEGER.4." }
end
subroutine foo(i4, i4a, i8, i8a)
- integer(kind=7) i4a, i8a
+ integer(kind=7) i4a, i8a ! { dg-error "Kind 7 not supported for type INTEGER" }
integer(kind=8) i8
print *, i4, i4a
print *, i8, i8a
end ! { dg-error "Unexpected END statement" }
-! { dg-excess-errors "Unexpected end of file" }
+! { dg-error "Unexpected end of file" "" { target "*-*-*" } 0 }
interface operator ( .gt. )
end interface operator ! { dg-error "END INTERFACE OPERATOR" }
end program p ! { dg-error "END INTERFACE" }
-! { dg-excess-errors "Unexpected end of file" }
+! { dg-error "Unexpected end of file" "" { target "*-*-*" } 0 }
interface operator ( .gt. )
end interface operator (.lt.) ! { dg-error "END INTERFACE OPERATOR" }
end program p ! { dg-error "END INTERFACE" }
-! { dg-excess-errors "Unexpected end of file" }
+! { dg-error "Unexpected end of file" "" { target "*-*-*" } 0 }
end subroutine foo
end
! { dg-error "Line truncated" " " { target *-*-* } 8 }
-! { dg-excess-errors "some warnings being treated as errors" }
+! { dg-prune-output "some warnings being treated as errors" }
end
! { dg-error "Line truncated" " " { target *-*-* } 3 }
! { dg-error "Unterminated character constant" " " { target *-*-* } 3 }
-! { dg-excess-errors "some warnings being treated as errors" }
+! { dg-prune-output "some warnings being treated as errors" }
!
print *, 1 + 2 ! { dg-error "Line truncated at .1." }
end
-! { dg-excess-errors "some warnings being treated as errors" }
+! { dg-prune-output "some warnings being treated as errors" }
!
print *, 1 + 2 ! { dg-error "Line truncated at .1." }
end
-! { dg-excess-errors "some warnings being treated as errors" }
+! { dg-prune-output "some warnings being treated as errors" }
!
print *, 1 + 2 ! { dg-error "Line truncated at .1." }
end
-! { dg-excess-errors "some warnings being treated as errors" }
+! { dg-prune-output "some warnings being treated as errors" }
end block i ! { dg-error "Expecting END PROGRAM statement" }
print*,i ! { dg-error "not appropriate for an expression" }
end
-! { dg-excess-errors "Unexpected end of file" }
+! { dg-error "Unexpected end of file" "" { target "*-*-*" } 0 }
do
end block ! { dg-error "Expecting END DO statement" }
end ! { dg-error "END DO statement expected" }
-! { dg-excess-errors "Unexpected end of file" }
+! { dg-error "Unexpected end of file" "" { target "*-*-*" } 0 }
USE MainModule
WRITE(*,*) a
END PROGRAM MyProg
-! { dg-excess-errors "does not contain a MODULE PROCEDURE" }
+! { dg-error "does not contain a MODULE PROCEDURE" "" { target "*-*-*" } 0 }
+! { dg-prune-output "compilation terminated" }
! { dg-error "Nonconforming tab character in column 1 of line 13" "Nonconforming tab" { target *-*-* } 0 }
! { dg-error "Nonconforming tab character in column 1 of line 14" "Nonconforming tab" { target *-*-* } 0 }
! { dg-error "Nonconforming tab character in column 1 of line 15" "Nonconforming tab" { target *-*-* } 0 }
-! { dg-excess-errors "some warnings being treated as errors" }
+! { dg-prune-output "some warnings being treated as errors" }
TYPE t
INTEGER :: x
- CONTAINS ! { dg-error "Fortran 2003" }
- PROCEDURE proc1 ! { dg-error "Fortran 2003" }
- PROCEDURE :: proc2 => p2 ! { dg-error "Fortran 2003" }
- END TYPE t
+ CONTAINS ! { dg-error "Fortran 2003: CONTAINS block in derived type definition" }
+ PROCEDURE proc1 ! { dg-error "Fortran 2003: PROCEDURE statement" }
+ PROCEDURE :: proc2 => p2 ! { dg-error "Fortran 2003: PROCEDURE statement" }
+ END TYPE t ! { dg-error "Fortran 2008: Derived type definition at .1. with empty CONTAINS section" }
CONTAINS
- SUBROUTINE proc1 (me)
+ SUBROUTINE proc1 (me) ! { dg-error "no IMPLICIT type" }
IMPLICIT NONE
- TYPE(t1) :: me
+ TYPE(t1) :: me ! { dg-error "being used before it is defined" }
END SUBROUTINE proc1
- REAL FUNCTION proc2 (me, x)
+ REAL FUNCTION proc2 (me, x) ! { dg-error "no IMPLICIT type" }
IMPLICIT NONE
- TYPE(t1) :: me
+ TYPE(t1) :: me ! { dg-error "being used before it is defined" }
REAL :: x
proc2 = x / 2
END FUNCTION proc2
END MODULE testmod
-! { dg-excess-errors "no IMPLICIT type" }
end
! { dg-final { output-exists-not } }
-! { dg-excess-errors "warnings being treated as errors" }
+! { dg-prune-output "warnings being treated as errors" }