aboutsummaryrefslogtreecommitdiff
path: root/gcc
diff options
context:
space:
mode:
authorTobias Burnus <burnus@gcc.gnu.org>2011-02-18 17:04:10 +0100
committerTobias Burnus <burnus@gcc.gnu.org>2011-02-18 17:04:10 +0100
commite23541755f8ded87da6b3056562ba9736d0126ee (patch)
tree1641647b08a6c6cc2238fd27a587000b13dba8e6 /gcc
parent12d80acc4898f08ea2abbfd8c2be41a52c8d98bc (diff)
downloadgcc-e23541755f8ded87da6b3056562ba9736d0126ee.zip
gcc-e23541755f8ded87da6b3056562ba9736d0126ee.tar.gz
gcc-e23541755f8ded87da6b3056562ba9736d0126ee.tar.bz2
re PR fortran/47750 (testsuite/gfortran.dg: dg-warning and dg-error should be distinguished)
2011-02-15 Tobias Burnus <burnus@net-b.de> PR fortran/47750 * lib/gfortran.exp (gfortran_init): Set gcc_error_prefix and gcc_warning_prefix. * lib/gfortran-dg.exp (gfortran-dg-test): Update regexp for normalizing the error/warning output. * gfortran.dg/Wall.f90: Update dg-error/warning. * gfortran.dg/argument_checking_15.f90: Update dg-error/warning. * gfortran.dg/argument_checking_3.f90: Update dg-error/warning. * gfortran.dg/argument_checking_6.f90: Update dg-error/warning. * gfortran.dg/bounds_temporaries_1.f90: Update dg-error/warning. * gfortran.dg/class_30.f90: Update dg-error/warning. * gfortran.dg/continuation_1.f90: Update dg-error/warning. * gfortran.dg/continuation_9.f90: Update dg-error/warning. * gfortran.dg/do_check_5.f90: Update dg-error/warning. * gfortran.dg/entry_17.f90: Update dg-error/warning. * gfortran.dg/entry_19.f90: Update dg-error/warning. * gfortran.dg/fmt_error.f90: Update dg-error/warning. * gfortran.dg/fmt_read_2.f90: Update dg-error/warning. * gfortran.dg/g77/12632.f: Update dg-error/warning. * gfortran.dg/g77/970625-2.f: Update dg-error/warning. * gfortran.dg/g77/980615-0.f: Update dg-error/warning. * gfortran.dg/generic_actual_arg.f90: Update dg-error/warning. * gfortran.dg/global_references_1.f90: Update dg-error/warning. * gfortran.dg/goto_8.f90: Update dg-error/warning. * gfortran.dg/initialization_1.f90: Update dg-error/warning. * gfortran.dg/io_constraints_1.f90: Update dg-error/warning. * gfortran.dg/io_constraints_2.f90: Update dg-error/warning. * gfortran.dg/io_constraints_3.f90: Update dg-error/warning. * gfortran.dg/iostat_3.f90: Update dg-error/warning. * gfortran.dg/public_private_module.f90: Update * dg-error/warning. * gfortran.dg/volatile3.f90: Update dg-error/warning. * gfortran.dg/warning-directive-2.F90: Update dg-error/warning. * gfortran.dg/warnings_are_errors_1.f: Update dg-error/warning. * gfortran.dg/whole_file_1.f90: Update dg-error/warning. * gfortran.dg/whole_file_2.f90: Update dg-error/warning. * gfortran.dg/whole_file_3.f90: Update dg-error/warning. From-SVN: r170273
Diffstat (limited to 'gcc')
-rw-r--r--gcc/testsuite/ChangeLog41
-rw-r--r--gcc/testsuite/gfortran.dg/Wall.f902
-rw-r--r--gcc/testsuite/gfortran.dg/argument_checking_15.f904
-rw-r--r--gcc/testsuite/gfortran.dg/argument_checking_3.f906
-rw-r--r--gcc/testsuite/gfortran.dg/argument_checking_6.f902
-rw-r--r--gcc/testsuite/gfortran.dg/bounds_temporaries_1.f902
-rw-r--r--gcc/testsuite/gfortran.dg/class_30.f904
-rw-r--r--gcc/testsuite/gfortran.dg/continuation_1.f902
-rw-r--r--gcc/testsuite/gfortran.dg/continuation_9.f906
-rw-r--r--gcc/testsuite/gfortran.dg/do_check_5.f904
-rw-r--r--gcc/testsuite/gfortran.dg/entry_17.f904
-rw-r--r--gcc/testsuite/gfortran.dg/entry_19.f902
-rw-r--r--gcc/testsuite/gfortran.dg/fmt_error.f902
-rw-r--r--gcc/testsuite/gfortran.dg/fmt_read_2.f904
-rw-r--r--gcc/testsuite/gfortran.dg/g77/12632.f2
-rw-r--r--gcc/testsuite/gfortran.dg/g77/970625-2.f2
-rw-r--r--gcc/testsuite/gfortran.dg/g77/980615-0.f2
-rw-r--r--gcc/testsuite/gfortran.dg/generic_actual_arg.f902
-rw-r--r--gcc/testsuite/gfortran.dg/global_references_1.f902
-rw-r--r--gcc/testsuite/gfortran.dg/goto_8.f904
-rw-r--r--gcc/testsuite/gfortran.dg/initialization_1.f902
-rw-r--r--gcc/testsuite/gfortran.dg/io_constraints_1.f904
-rw-r--r--gcc/testsuite/gfortran.dg/io_constraints_2.f902
-rw-r--r--gcc/testsuite/gfortran.dg/io_constraints_3.f908
-rw-r--r--gcc/testsuite/gfortran.dg/iostat_3.f904
-rw-r--r--gcc/testsuite/gfortran.dg/public_private_module.f904
-rw-r--r--gcc/testsuite/gfortran.dg/volatile3.f902
-rw-r--r--gcc/testsuite/gfortran.dg/warning-directive-2.F902
-rw-r--r--gcc/testsuite/gfortran.dg/warnings_are_errors_1.f2
-rw-r--r--gcc/testsuite/gfortran.dg/whole_file_1.f904
-rw-r--r--gcc/testsuite/gfortran.dg/whole_file_2.f904
-rw-r--r--gcc/testsuite/gfortran.dg/whole_file_3.f904
-rw-r--r--gcc/testsuite/lib/gfortran-dg.exp19
-rw-r--r--gcc/testsuite/lib/gfortran.exp5
34 files changed, 110 insertions, 55 deletions
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index 595db76..1076e32 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,42 @@
+2011-02-15 Tobias Burnus <burnus@net-b.de>
+
+ PR fortran/47750
+ * lib/gfortran.exp (gfortran_init): Set gcc_error_prefix and
+ gcc_warning_prefix.
+ * lib/gfortran-dg.exp (gfortran-dg-test): Update regexp for
+ normalizing the error/warning output.
+ * gfortran.dg/Wall.f90: Update dg-error/warning.
+ * gfortran.dg/argument_checking_15.f90: Update dg-error/warning.
+ * gfortran.dg/argument_checking_3.f90: Update dg-error/warning.
+ * gfortran.dg/argument_checking_6.f90: Update dg-error/warning.
+ * gfortran.dg/bounds_temporaries_1.f90: Update dg-error/warning.
+ * gfortran.dg/class_30.f90: Update dg-error/warning.
+ * gfortran.dg/continuation_1.f90: Update dg-error/warning.
+ * gfortran.dg/continuation_9.f90: Update dg-error/warning.
+ * gfortran.dg/do_check_5.f90: Update dg-error/warning.
+ * gfortran.dg/entry_17.f90: Update dg-error/warning.
+ * gfortran.dg/entry_19.f90: Update dg-error/warning.
+ * gfortran.dg/fmt_error.f90: Update dg-error/warning.
+ * gfortran.dg/fmt_read_2.f90: Update dg-error/warning.
+ * gfortran.dg/g77/12632.f: Update dg-error/warning.
+ * gfortran.dg/g77/970625-2.f: Update dg-error/warning.
+ * gfortran.dg/g77/980615-0.f: Update dg-error/warning.
+ * gfortran.dg/generic_actual_arg.f90: Update dg-error/warning.
+ * gfortran.dg/global_references_1.f90: Update dg-error/warning.
+ * gfortran.dg/goto_8.f90: Update dg-error/warning.
+ * gfortran.dg/initialization_1.f90: Update dg-error/warning.
+ * gfortran.dg/io_constraints_1.f90: Update dg-error/warning.
+ * gfortran.dg/io_constraints_2.f90: Update dg-error/warning.
+ * gfortran.dg/io_constraints_3.f90: Update dg-error/warning.
+ * gfortran.dg/iostat_3.f90: Update dg-error/warning.
+ * gfortran.dg/public_private_module.f90: Update dg-error/warning.
+ * gfortran.dg/volatile3.f90: Update dg-error/warning.
+ * gfortran.dg/warning-directive-2.F90: Update dg-error/warning.
+ * gfortran.dg/warnings_are_errors_1.f: Update dg-error/warning.
+ * gfortran.dg/whole_file_1.f90: Update dg-error/warning.
+ * gfortran.dg/whole_file_2.f90: Update dg-error/warning.
+ * gfortran.dg/whole_file_3.f90: Update dg-error/warning.
+
2011-02-18 Janus Weil <janus@gcc.gnu.org>
PR fortran/47768
@@ -15,7 +54,7 @@
2011-02-18 Dodji Seketeli <dodji@redhat.com>
- PR c++/47208
+ PR c++/47208
* g++.dg/cpp0x/auto21.C: New test.
2011-02-17 Iain Sandoe <iains@gcc.gnu.org>
diff --git a/gcc/testsuite/gfortran.dg/Wall.f90 b/gcc/testsuite/gfortran.dg/Wall.f90
index a11c4b7..64c95a9 100644
--- a/gcc/testsuite/gfortran.dg/Wall.f90
+++ b/gcc/testsuite/gfortran.dg/Wall.f90
@@ -5,7 +5,7 @@ program main
character (len=40) &
c
c = "Hello, &
- world!" ! { dg-warning "Warning: Missing '&' in continued character constant" }
+ world!" ! { dg-warning "Missing '&' in continued character constant" }
if (c.ne.&
"Hello, world!")&
call abort();end program main
diff --git a/gcc/testsuite/gfortran.dg/argument_checking_15.f90 b/gcc/testsuite/gfortran.dg/argument_checking_15.f90
index 90046bb..5d3c9f6 100644
--- a/gcc/testsuite/gfortran.dg/argument_checking_15.f90
+++ b/gcc/testsuite/gfortran.dg/argument_checking_15.f90
@@ -45,8 +45,8 @@ subroutine test()
implicit none
character(len=5), pointer :: c
character(len=5) :: str(5)
-call foo(c) ! { dg-error "Character length mismatch" }
-call bar(str) ! { dg-error "Character length mismatch" }
+call foo(c) ! { dg-warning "Character length mismatch" }
+call bar(str) ! { dg-warning "Character length mismatch" }
contains
subroutine foo(a)
character(len=3), pointer :: a
diff --git a/gcc/testsuite/gfortran.dg/argument_checking_3.f90 b/gcc/testsuite/gfortran.dg/argument_checking_3.f90
index 1e01c1f..5f451bf 100644
--- a/gcc/testsuite/gfortran.dg/argument_checking_3.f90
+++ b/gcc/testsuite/gfortran.dg/argument_checking_3.f90
@@ -22,9 +22,9 @@ end interface
len2 = '12'
len4 = '1234'
- call foo(len2) ! { dg-warning "Rank mismatch in argument" }
- call foo("ca") ! { dg-warning "Rank mismatch in argument" }
- call bar("ca") ! { dg-warning "Rank mismatch in argument" }
+ call foo(len2) ! { dg-error "Rank mismatch in argument" }
+ call foo("ca") ! { dg-error "Rank mismatch in argument" }
+ call bar("ca") ! { dg-error "Rank mismatch in argument" }
call foobar(len2) ! { dg-warning "contains too few elements" }
call foobar(len4)
call foobar("bar") ! { dg-warning "contains too few elements" }
diff --git a/gcc/testsuite/gfortran.dg/argument_checking_6.f90 b/gcc/testsuite/gfortran.dg/argument_checking_6.f90
index 3742ab6..e2d2692 100644
--- a/gcc/testsuite/gfortran.dg/argument_checking_6.f90
+++ b/gcc/testsuite/gfortran.dg/argument_checking_6.f90
@@ -14,7 +14,7 @@ real,dimension(-1:2) :: z
call sub(x(:))
call sub(y(:))
call sub(z(:))
-call sub(w(:)) ! { dg-error "too few elements" }
+call sub(w(:)) ! { dg-warning "too few elements" }
contains
subroutine sub(a)
diff --git a/gcc/testsuite/gfortran.dg/bounds_temporaries_1.f90 b/gcc/testsuite/gfortran.dg/bounds_temporaries_1.f90
index 32bb265..44b5a7d 100644
--- a/gcc/testsuite/gfortran.dg/bounds_temporaries_1.f90
+++ b/gcc/testsuite/gfortran.dg/bounds_temporaries_1.f90
@@ -22,7 +22,7 @@ end subroutine gfcbug34
! This is PR25669
subroutine foo (a)
real a(*)
- call bar (a, LBOUND(a),2) ! { dg-warning "Rank mismatch in argument" }
+ call bar (a, LBOUND(a),2) ! { dg-error "Rank mismatch in argument" }
end subroutine foo
subroutine bar (b, i, j)
real b(i:j)
diff --git a/gcc/testsuite/gfortran.dg/class_30.f90 b/gcc/testsuite/gfortran.dg/class_30.f90
index f81e614..f2cedcb 100644
--- a/gcc/testsuite/gfortran.dg/class_30.f90
+++ b/gcc/testsuite/gfortran.dg/class_30.f90
@@ -14,6 +14,8 @@ type t2
end type t2
type, bind(C):: t3
- class(t), pointer :: y ! { dg-error "may not be C interoperable|Polymorphic component y at .1. in SEQUENCE or BIND" }
+ class(t), pointer :: y
+ ! { dg-warning "may not be C interoperable" "" { target *-*-* } 17 }
+ ! { dg-error "Polymorphic component y at .1. in SEQUENCE or BIND" "" { target *-*-* } 17 }
end type t3
end
diff --git a/gcc/testsuite/gfortran.dg/continuation_1.f90 b/gcc/testsuite/gfortran.dg/continuation_1.f90
index 64a98ad..1036db9 100644
--- a/gcc/testsuite/gfortran.dg/continuation_1.f90
+++ b/gcc/testsuite/gfortran.dg/continuation_1.f90
@@ -8,7 +8,7 @@ program main
character (len=40) &
c
c = "Hello, &
- world!" ! { dg-warning "Warning: Missing '&' in continued character constant" }
+ world!" ! { dg-warning "Missing '&' in continued character constant" }
if (c.ne.&
"Hello, world!")&
call abort();end program main
diff --git a/gcc/testsuite/gfortran.dg/continuation_9.f90 b/gcc/testsuite/gfortran.dg/continuation_9.f90
index 7cd9c9d..04a7c33 100644
--- a/gcc/testsuite/gfortran.dg/continuation_9.f90
+++ b/gcc/testsuite/gfortran.dg/continuation_9.f90
@@ -4,6 +4,6 @@
&
&
end
-! { dg-error "not allowed by itself in line 3" "" {target "*-*-*"} 0 }
-! { dg-error "not allowed by itself in line 4" "" {target "*-*-*"} 0 }
-! { dg-error "not allowed by itself in line 5" "" {target "*-*-*"} 0 }
+! { dg-warning "not allowed by itself in line 3" "" {target "*-*-*"} 0 }
+! { dg-warning "not allowed by itself in line 4" "" {target "*-*-*"} 0 }
+! { dg-warning "not allowed by itself in line 5" "" {target "*-*-*"} 0 }
diff --git a/gcc/testsuite/gfortran.dg/do_check_5.f90 b/gcc/testsuite/gfortran.dg/do_check_5.f90
index 081a228..3df7b14 100644
--- a/gcc/testsuite/gfortran.dg/do_check_5.f90
+++ b/gcc/testsuite/gfortran.dg/do_check_5.f90
@@ -27,6 +27,8 @@ end do
do r = 1, 2, -1 ! { dg-warning "must be integer|executed zero times" }
end do
-do r = 1, 2, 0 ! { dg-error "must be integer|cannot be zero" }
+do r = 1, 2, 0
end do
+! { dg-warning "must be integer" "loop var" { target *-*-* } 30 }
+! { dg-error "cannot be zero" "loop step" { target *-*-* } 30 }
end
diff --git a/gcc/testsuite/gfortran.dg/entry_17.f90 b/gcc/testsuite/gfortran.dg/entry_17.f90
index b4e91c2..5671cfe 100644
--- a/gcc/testsuite/gfortran.dg/entry_17.f90
+++ b/gcc/testsuite/gfortran.dg/entry_17.f90
@@ -26,7 +26,7 @@ entry bar3()
bar3 = ""
end function test3
-function test4(n) ! { dg-error "returning variables of different string lengths" }
+function test4(n) ! { dg-warning "returning variables of different string lengths" }
integer :: n
character(n) :: test4
character(*) :: bar4 ! { dg-warning "Obsolescent feature" }
@@ -36,7 +36,7 @@ entry bar4()
bar4 = ""
end function test4
-function test5() ! { dg-error "returning variables of different string lengths" }
+function test5() ! { dg-warning "returning variables of different string lengths" }
character(1) :: test5
character(2) :: bar5
test5 = ""
diff --git a/gcc/testsuite/gfortran.dg/entry_19.f90 b/gcc/testsuite/gfortran.dg/entry_19.f90
index b7b8bfa..87b52ad 100644
--- a/gcc/testsuite/gfortran.dg/entry_19.f90
+++ b/gcc/testsuite/gfortran.dg/entry_19.f90
@@ -5,5 +5,5 @@
! Entry is obsolete in Fortran 2008
!
subroutine foo()
-entry bar() ! { dg-error "Fortran 2008 obsolescent feature: ENTRY" }
+entry bar() ! { dg-warning "Fortran 2008 obsolescent feature: ENTRY" }
end
diff --git a/gcc/testsuite/gfortran.dg/fmt_error.f90 b/gcc/testsuite/gfortran.dg/fmt_error.f90
index 45d5855..7dc2ab6 100644
--- a/gcc/testsuite/gfortran.dg/fmt_error.f90
+++ b/gcc/testsuite/gfortran.dg/fmt_error.f90
@@ -1,4 +1,4 @@
! { dg-do compile }
! PR32545 Give compile error not warning for wrong edit format statements.
-read (5,'(i0)') i ! { dg-error "Error: Positive width required in format" }
+read (5,'(i0)') i ! { dg-error "Positive width required in format" }
end
diff --git a/gcc/testsuite/gfortran.dg/fmt_read_2.f90 b/gcc/testsuite/gfortran.dg/fmt_read_2.f90
index 0f7f4d7..316f737 100644
--- a/gcc/testsuite/gfortran.dg/fmt_read_2.f90
+++ b/gcc/testsuite/gfortran.dg/fmt_read_2.f90
@@ -4,7 +4,7 @@
integer :: r
real :: a
write (*,'(i0)') r
- read (*,'(i0)') r ! { dg-warning "Positive width required" }
- read (*,'(f0.2)') a ! { dg-warning "Positive width required" }
+ read (*,'(i0)') r ! { dg-error "Positive width required" }
+ read (*,'(f0.2)') a ! { dg-error "Positive width required" }
print *, r,a
END
diff --git a/gcc/testsuite/gfortran.dg/g77/12632.f b/gcc/testsuite/gfortran.dg/g77/12632.f
index 91121c8..3983339 100644
--- a/gcc/testsuite/gfortran.dg/g77/12632.f
+++ b/gcc/testsuite/gfortran.dg/g77/12632.f
@@ -1,6 +1,6 @@
C { dg-do compile }
C { dg-options "-fbounds-check" }
INTEGER I(1)
- I(2) = 0 ! { dg-error "out of bounds" "out of bounds" }
+ I(2) = 0 ! { dg-warning "out of bounds" "out of bounds" }
END
diff --git a/gcc/testsuite/gfortran.dg/g77/970625-2.f b/gcc/testsuite/gfortran.dg/g77/970625-2.f
index 19bd096..7f8a464 100644
--- a/gcc/testsuite/gfortran.dg/g77/970625-2.f
+++ b/gcc/testsuite/gfortran.dg/g77/970625-2.f
@@ -40,7 +40,7 @@
PROGRAM = THEN - IF
ELSE IF = THEN .GT. IF
IF (THEN.GT.REAL) THEN
- CALL FUNCTION PROGRAM (ELSE IF, GO TO PROGRAM, THEN) ! { dg-warning "Type mismatch in argument" }
+ CALL FUNCTION PROGRAM (ELSE IF, GO TO PROGRAM, THEN) ! { dg-error "Type mismatch in argument" }
ELSE IF (ELSE IF) THEN
REAL = THEN + END DO
END IF
diff --git a/gcc/testsuite/gfortran.dg/g77/980615-0.f b/gcc/testsuite/gfortran.dg/g77/980615-0.f
index 7e1f14f..5107f4f 100644
--- a/gcc/testsuite/gfortran.dg/g77/980615-0.f
+++ b/gcc/testsuite/gfortran.dg/g77/980615-0.f
@@ -8,5 +8,5 @@ c { dg-do compile }
CaLL foo(W)
END
SUBROUTINE foo(W)
- yy(I)=A(I)Q(X) ! { dg-error "Error: Unclassifiable statement" "" }
+ yy(I)=A(I)Q(X) ! { dg-error "Unclassifiable statement" "" }
c { dg-error "end of file" "end of file" { target *-*-* } 0 }
diff --git a/gcc/testsuite/gfortran.dg/generic_actual_arg.f90 b/gcc/testsuite/gfortran.dg/generic_actual_arg.f90
index e0b36a0..17c5062 100644
--- a/gcc/testsuite/gfortran.dg/generic_actual_arg.f90
+++ b/gcc/testsuite/gfortran.dg/generic_actual_arg.f90
@@ -37,7 +37,7 @@ USE TEST
USE TEST2
CALL F(CALCULATION) ! { dg-error "GENERIC procedure" }
-CALL F(CALCULATION2) ! OK because there is a same name specific, but: ! { dg-warning "More actual than formal arguments" }
+CALL F(CALCULATION2) ! OK because there is a same name specific, but: ! { dg-error "More actual than formal arguments" }
END
SUBROUTINE F()
diff --git a/gcc/testsuite/gfortran.dg/global_references_1.f90 b/gcc/testsuite/gfortran.dg/global_references_1.f90
index d241aca..7e0a5bd 100644
--- a/gcc/testsuite/gfortran.dg/global_references_1.f90
+++ b/gcc/testsuite/gfortran.dg/global_references_1.f90
@@ -32,7 +32,7 @@ function h(x) ! { dg-error "is already being used as a FUNCTION" }
end function h
SUBROUTINE TT()
- CHARACTER(LEN=10), EXTERNAL :: j ! { dg-warning "Return type mismatch" }
+ CHARACTER(LEN=10), EXTERNAL :: j ! { dg-error "Return type mismatch" }
CHARACTER(LEN=10) :: T
! PR20881===========================================================
! Error only appears once but testsuite associates with both lines.
diff --git a/gcc/testsuite/gfortran.dg/goto_8.f90 b/gcc/testsuite/gfortran.dg/goto_8.f90
index a5f1f7f..744b5f3 100644
--- a/gcc/testsuite/gfortran.dg/goto_8.f90
+++ b/gcc/testsuite/gfortran.dg/goto_8.f90
@@ -23,9 +23,9 @@ end block
88 continue
! 3rd example: jumping into BLOCK (invalid)
-goto 99 ! { dg-error "is not in the same block" }
+goto 99 ! { dg-warning "is not in the same block" }
block
- 99 continue ! { dg-error "is not in the same block" }
+ 99 continue ! { dg-warning "is not in the same block" }
end block
end
diff --git a/gcc/testsuite/gfortran.dg/initialization_1.f90 b/gcc/testsuite/gfortran.dg/initialization_1.f90
index 3ca20ac..2fb014e 100644
--- a/gcc/testsuite/gfortran.dg/initialization_1.f90
+++ b/gcc/testsuite/gfortran.dg/initialization_1.f90
@@ -24,7 +24,7 @@ contains
real :: z(2, 2)
! However, this gives a warning because it is an initialization expression.
- integer :: l1 = len (ch1) ! { dg-warning "Assumed or deferred character length variable" }
+ integer :: l1 = len (ch1) ! { dg-error "Assumed or deferred character length variable" }
! These are warnings because they are gfortran extensions.
integer :: m3 = size (x, 1) ! { dg-error "Assumed size array" }
diff --git a/gcc/testsuite/gfortran.dg/io_constraints_1.f90 b/gcc/testsuite/gfortran.dg/io_constraints_1.f90
index db1e949..eb8ab8d 100644
--- a/gcc/testsuite/gfortran.dg/io_constraints_1.f90
+++ b/gcc/testsuite/gfortran.dg/io_constraints_1.f90
@@ -33,7 +33,7 @@ end module global
! Appending to a USE associated namelist is an extension.
- NAMELIST /NL/ a,b ! { dg-warning "already is USE associated" }
+ NAMELIST /NL/ a,b ! { dg-error "already is USE associated" }
a=1 ; b=2
@@ -54,7 +54,7 @@ end module global
! R912
!Was correctly picked up before patch.
- write(6, NML=NL, iostat = ierr) ! { dg-warning "requires default INTEGER" }
+ write(6, NML=NL, iostat = ierr) ! { dg-error "requires default INTEGER" }
! Constraints
!Was correctly picked up before patch.
diff --git a/gcc/testsuite/gfortran.dg/io_constraints_2.f90 b/gcc/testsuite/gfortran.dg/io_constraints_2.f90
index 8d3ae6b..42aba66 100644
--- a/gcc/testsuite/gfortran.dg/io_constraints_2.f90
+++ b/gcc/testsuite/gfortran.dg/io_constraints_2.f90
@@ -30,7 +30,7 @@ end module global
! Appending to a USE associated namelist is an extension.
- NAMELIST /NL/ a,b ! { dg-warning "already is USE associated" }
+ NAMELIST /NL/ a,b ! { dg-error "already is USE associated" }
a=1 ; b=2
diff --git a/gcc/testsuite/gfortran.dg/io_constraints_3.f90 b/gcc/testsuite/gfortran.dg/io_constraints_3.f90
index ae9acce..7622a24 100644
--- a/gcc/testsuite/gfortran.dg/io_constraints_3.f90
+++ b/gcc/testsuite/gfortran.dg/io_constraints_3.f90
@@ -44,8 +44,8 @@
open(10, iostat=u,position="append")
open(10, iostat=u,position=foo) ! { dg-warning "POSITION specifier in OPEN statement" }
- open(10, iostat=u,recl="ee") ! { dg-warning "must be of type INTEGER" }
- open(10, iostat=u,recl=0.4) ! { dg-warning "must be of type INTEGER" }
+ open(10, iostat=u,recl="ee") ! { dg-error "must be of type INTEGER" }
+ open(10, iostat=u,recl=0.4) ! { dg-error "must be of type INTEGER" }
open(10, iostat=u,recl=zero) ! { dg-warning "must be positive" }
open(10, iostat=u,recl=mone) ! { dg-warning "must be positive" }
@@ -105,8 +105,8 @@
open(10, err=99,position="append")
open(10, err=99,position=foo) ! { dg-warning "POSITION specifier in OPEN statement" }
- open(10, err=99,recl="ee") ! { dg-warning "must be of type INTEGER" }
- open(10, err=99,recl=0.4) ! { dg-warning "must be of type INTEGER" }
+ open(10, err=99,recl="ee") ! { dg-error "must be of type INTEGER" }
+ open(10, err=99,recl=0.4) ! { dg-error "must be of type INTEGER" }
open(10, err=99,recl=zero) ! { dg-warning "must be positive" }
open(10, err=99,recl=mone) ! { dg-warning "must be positive" }
diff --git a/gcc/testsuite/gfortran.dg/iostat_3.f90 b/gcc/testsuite/gfortran.dg/iostat_3.f90
index 0f6aaca..23492f2 100644
--- a/gcc/testsuite/gfortran.dg/iostat_3.f90
+++ b/gcc/testsuite/gfortran.dg/iostat_3.f90
@@ -4,6 +4,6 @@
real :: u
integer(kind=8) :: i
open (10,status="scratch")
- read (10,*,iostat=i) u ! { dg-warning "Fortran 95 requires default INTEGER in IOSTAT tag" }
- close (10,iostat=i) ! { dg-warning "Fortran 95 requires default INTEGER in IOSTAT tag" }
+ read (10,*,iostat=i) u ! { dg-error "Fortran 95 requires default INTEGER in IOSTAT tag" }
+ close (10,iostat=i) ! { dg-error "Fortran 95 requires default INTEGER in IOSTAT tag" }
end
diff --git a/gcc/testsuite/gfortran.dg/public_private_module.f90 b/gcc/testsuite/gfortran.dg/public_private_module.f90
index ca1ab48..48e78b6 100644
--- a/gcc/testsuite/gfortran.dg/public_private_module.f90
+++ b/gcc/testsuite/gfortran.dg/public_private_module.f90
@@ -8,12 +8,12 @@ end module a
module b
use a
implicit none
- public a ! { dg-warning "attribute applied to" }
+ public a ! { dg-error "attribute applied to" }
end module b
module d
use a
implicit none
- private a ! { dg-warning "attribute applied to" }
+ private a ! { dg-error "attribute applied to" }
end module d
! { dg-final { cleanup-modules "a" } }
diff --git a/gcc/testsuite/gfortran.dg/volatile3.f90 b/gcc/testsuite/gfortran.dg/volatile3.f90
index 966272e..f9f7202 100644
--- a/gcc/testsuite/gfortran.dg/volatile3.f90
+++ b/gcc/testsuite/gfortran.dg/volatile3.f90
@@ -11,7 +11,7 @@ program volatile_test
real :: l,m
real,volatile :: n
real, volatile,volatile :: r = 3. ! { dg-error "Duplicate VOLATILE attribute" }
- volatile :: l,n ! { dg-error "Duplicate VOLATILE attribute" }
+ volatile :: l,n ! { dg-warning "Duplicate VOLATILE attribute" }
volatile ! { dg-error "Syntax error in VOLATILE statement" }
volatile :: volatile_test ! { dg-error "PROGRAM attribute conflicts with VOLATILE attribute" }
l = 4.0
diff --git a/gcc/testsuite/gfortran.dg/warning-directive-2.F90 b/gcc/testsuite/gfortran.dg/warning-directive-2.F90
index fa9460a..7e44185 100644
--- a/gcc/testsuite/gfortran.dg/warning-directive-2.F90
+++ b/gcc/testsuite/gfortran.dg/warning-directive-2.F90
@@ -1,5 +1,5 @@
! { dg-do preprocess }
! { dg-options "-std=f95 -fdiagnostics-show-option -Werror=cpp" }
-! { dg-warning "some warnings being treated as errors" "" {target "*-*-*"} 0 }
+! { dg-message "some warnings being treated as errors" "" {target "*-*-*"} 0 }
#warning "Printed"
! { dg-error "\"Printed\" .-Werror=cpp." "" { target *-*-* } 4 }
diff --git a/gcc/testsuite/gfortran.dg/warnings_are_errors_1.f b/gcc/testsuite/gfortran.dg/warnings_are_errors_1.f
index 3d163bb..56465a9 100644
--- a/gcc/testsuite/gfortran.dg/warnings_are_errors_1.f
+++ b/gcc/testsuite/gfortran.dg/warnings_are_errors_1.f
@@ -12,7 +12,7 @@
!
34 5 i=0
! gfc_notify_std(GFC_STD_F95_DEL):
- do r1 = 1, 2 ! { dg-error "Deleted feature: Loop variable" }
+ do r1 = 1, 2 ! { dg-warning "Deleted feature: Loop variable" }
i = i+1
end do
call foo j bar
diff --git a/gcc/testsuite/gfortran.dg/whole_file_1.f90 b/gcc/testsuite/gfortran.dg/whole_file_1.f90
index d7137ee..598c9d3 100644
--- a/gcc/testsuite/gfortran.dg/whole_file_1.f90
+++ b/gcc/testsuite/gfortran.dg/whole_file_1.f90
@@ -19,7 +19,7 @@ subroutine b
integer :: u1
end type
type (u) :: q
- call a(q) ! { dg-error "Type mismatch" }
+ call a(q) ! { dg-warning "Type mismatch" }
print *, q%u1
end subroutine
@@ -36,7 +36,7 @@ subroutine d
integer :: u1
end type
type (u) :: q
- call c(q) ! { dg-error "Type mismatch" }
+ call c(q) ! { dg-warning "Type mismatch" }
print *, q%u1
end subroutine
diff --git a/gcc/testsuite/gfortran.dg/whole_file_2.f90 b/gcc/testsuite/gfortran.dg/whole_file_2.f90
index 7f40352..4e33c06 100644
--- a/gcc/testsuite/gfortran.dg/whole_file_2.f90
+++ b/gcc/testsuite/gfortran.dg/whole_file_2.f90
@@ -14,8 +14,8 @@ end function
program gg
real :: h
character (5) :: chr = 'hello'
-h = a(); ! { dg-error "Missing actual argument" }
-call test ([chr]) ! { dg-error "Rank mismatch" }
+h = a(); ! { dg-warning "Missing actual argument" }
+call test ([chr]) ! { dg-warning "Rank mismatch" }
end program gg
subroutine test (a)
diff --git a/gcc/testsuite/gfortran.dg/whole_file_3.f90 b/gcc/testsuite/gfortran.dg/whole_file_3.f90
index 7ad762c..242280c 100644
--- a/gcc/testsuite/gfortran.dg/whole_file_3.f90
+++ b/gcc/testsuite/gfortran.dg/whole_file_3.f90
@@ -14,8 +14,8 @@
program test
EXTERNAL R
- call PHLOAD (R, 1) ! { dg-error "Missing alternate return spec" }
- CALL PHLOAD (R, 2) ! { dg-error "Missing alternate return spec" }
+ call PHLOAD (R, 1) ! { dg-warning "Missing alternate return spec" }
+ CALL PHLOAD (R, 2) ! { dg-warning "Missing alternate return spec" }
CALL PHLOAD (R, *999) ! This one is OK
999 continue
END program test
diff --git a/gcc/testsuite/lib/gfortran-dg.exp b/gcc/testsuite/lib/gfortran-dg.exp
index 70a0888..0fd96b3 100644
--- a/gcc/testsuite/lib/gfortran-dg.exp
+++ b/gcc/testsuite/lib/gfortran-dg.exp
@@ -52,23 +52,30 @@ proc gfortran-dg-test { prog do_what extra_tool_flags } {
# Where [locus] is either [line] or [line].[columns] .
#
# We collapse these to look like:
- # [name]:[line]: Error: Some error at (1) and (2)
+ # [name]:[line]:[column]: Error: Some error at (1) and (2)
# or
- # [name]:[line]: Error: Some error at (1) and (2)
- # [name]:[line2]: Error: Some error at (1) and (2)
+ # [name]:[line]:[column]: Error: Some error at (1) and (2)
+ # [name]:[line2]:[column]: Error: Some error at (1) and (2)
# We proceed in two steps: first we deal with the form with two
# different locus lines, then with the form with only one locus line.
#
# Note that these regexps only make sense in the combinations used below.
# Note also that is imperative that we first deal with the form with
# two loci.
- set locus_regexp "(\[^\n\]*):(\[0-9\]*)\[^\n\]*:\n\n\[^\n\]*\n\[^\n\]*\n"
+ set locus_regexp "(\[^\n\]*):(\[0-9\]+)\[\.:\](\[0-9\]*)(-\[0-9\]*)?:\n\n\[^\n\]*\n\[^\n\]*\n"
set diag_regexp "(\[^\n\]*)\n"
+ # Add column number if none exists
+ set colnum_regexp "(Warning: |Error: )?(\[^\n\]*):(\[0-9\]+):(\[ \n\])"
+ regsub -all $colnum_regexp $comp_output "\\2:\\3:0:\\4\\1" comp_output
+
set two_loci "$locus_regexp$locus_regexp$diag_regexp"
set single_locus "$locus_regexp$diag_regexp"
- regsub -all $two_loci $comp_output "\\1:\\2: \\5\n\\3:\\4: \\5\n" comp_output
- regsub -all $single_locus $comp_output "\\1:\\2: \\3\n" comp_output
+ regsub -all $two_loci $comp_output "\\1:\\2:\\3: \\9\n\\5:\\6:\\7: \\9\n" comp_output
+ regsub -all $single_locus $comp_output "\\1:\\2:\\3: \\5\n" comp_output
+
+ # Add a line number if none exists
+ regsub -all "(^|\n)(Warning: |Error: )" $comp_output "\\1:0:0: \\2" comp_output
return [list $comp_output $output_file]
}
diff --git a/gcc/testsuite/lib/gfortran.exp b/gcc/testsuite/lib/gfortran.exp
index 8c88550..4a1a636 100644
--- a/gcc/testsuite/lib/gfortran.exp
+++ b/gcc/testsuite/lib/gfortran.exp
@@ -142,11 +142,16 @@ proc gfortran_init { args } {
global TOOL_EXECUTABLE TOOL_OPTIONS
global GFORTRAN_UNDER_TEST
global TESTING_IN_BUILD_TREE
+ global gcc_warning_prefix
+ global gcc_error_prefix
# We set LC_ALL and LANG to C so that we get the same error messages as expected.
setenv LC_ALL C
setenv LANG C
+ set gcc_warning_prefix "\[Ww\]arning:"
+ set gcc_error_prefix "(Fatal )?\[Ee\]rror:"
+
# Many hosts now default to a non-ASCII C locale, however, so
# they can set a charset encoding here if they need.
if { [ishost "*-*-cygwin*"] } {