summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg
diff options
context:
space:
mode:
authorfxcoudert <fxcoudert@138bc75d-0d04-0410-961f-82ee72b054a4>2008-03-03 23:46:20 +0000
committerfxcoudert <fxcoudert@138bc75d-0d04-0410-961f-82ee72b054a4>2008-03-03 23:46:20 +0000
commitff4425cf07fc7f786626ddf647a34ea60c880286 (patch)
treeafdccf794dd7e07d887dd608052f12f5ea83ec70 /gcc/testsuite/gfortran.dg
parentab7cd804d13cec9d2e6247dced88286f8f4d8871 (diff)
downloadgcc-ff4425cf07fc7f786626ddf647a34ea60c880286.tar.gz
PR fortran/33197
gcc/fortran/ * intrinsic.c (add_functions): Modify intrinsics ACOSH, ASINH, ATANH, ERF, ERFC and GAMMA. Add intrinsics BESSEL_{J,Y}{0,1,N}, ERFC_SCALED, LOG_GAMMA and HYPOT. * intrinsic.h (gfc_check_hypot, gfc_simplify_hypot, gfc_resolve_hypot): New prototypes. * mathbuiltins.def: Add HYPOT builtin. Make complex versions of ACOSH, ASINH and ATANH available. * gfortran.h (GFC_ISYM_ERFC_SCALED, GFC_ISYM_HYPOT): New values. * lang.opt: Add -std=f2008 option. * libgfortran.h: Define GFC_STD_F2008. * lang-specs.h: Add .f08 and .F08 file suffixes. * iresolve.c (gfc_resolve_hypot): New function. * parse.c (parse_contained): Allow empty CONTAINS for Fortran 2008. * check.c (gfc_check_hypot): New function. * trans-intrinsic.c (gfc_intrinsic_map): Define ERFC_SCALE builtin. * options.c (set_default_std_flags): Allow Fortran 2008 by default. (form_from_filename): Add .f08 suffix. (gfc_handle_option): Handle -std=f2008 option. * simplify.c (gfc_simplify_hypot): New function. * gfortran.texi: Document Fortran 2008 status and file extensions. * intrinsic.texi: Document new BESSEL_{J,Y}{0,1,N} intrinsics, as well as HYPOT and ERFC_SCALED. Update documentation of ERF, ERFC, GAMMA, LGAMMA, ASINH, ACOSH and ATANH. * invoke.texi: Document the new -std=f2008 option. libgomp/ * testsuite/libgomp.fortran/fortran.exp: Add .f08 and .F08 file suffixes. gcc/testsuite/ * gfortran.dg/gomp/gomp.exp: Add .f08 and .F08 file suffixes. * gfortran.dg/dg.exp: Likewise. * gfortran.dg/vect/vect.exp: Likewise. * gfortran.fortran-torture/execute/execute.exp: Likewise. * gfortran.fortran-torture/compile/compile.exp: Likewise. * gfortran.dg/gamma_1.f90: Also check log_gamma. * gfortran.dg/invalid_contains_1.f90: Remove warning about empty CONTAINS. * gfortran.dg/gamma_2.f90: Add a few error messages. * gfortran.dg/invalid_contains_2.f90: Remove warning about empty CONTAINS. * gfortran.dg/gamma_3.f90: Adjust error message. * gfortran.dg/gamma_4.f90: Test for log_gamma instead of lgamma. * gfortran.dg/bind_c_usage_9.f03: Adjust error messages. * gfortran.dg/bessel_1.f90: New test. * gfortran.dg/recursive_check_3.f90: Remove warnings. * gfortran.dg/besxy.f90: Also check for new F2008 intrinsics. * gfortran.dg/derived_function_interface_1.f90: Remove warning. * gfortran.dg/contains_empty_1.f03: New test. * gfortran.dg/erfc_scaled_1.f90: New test. * gfortran.dg/hypot_1.f90: New test. * gfortran.dg/contains_empty_2.f03: New test. libgfortran/ * intrinsics/erfc_scaled_inc.c: New file. * intrinsics/erfc_scaled.c: New file. * gfortran.map (GFORTRAN_1.0): Add _gfortran_erfc_scaled_r*. * Makefile.am: Add intrinsics/erfc_scaled.c. * config.h.in: Regenerate. * configure: Regenerate. * Makefile.in: Regenerate. git-svn-id: svn+ssh://gcc.gnu.org/svn/gcc/trunk@132846 138bc75d-0d04-0410-961f-82ee72b054a4
Diffstat (limited to 'gcc/testsuite/gfortran.dg')
-rw-r--r--gcc/testsuite/gfortran.dg/bessel_1.f9037
-rw-r--r--gcc/testsuite/gfortran.dg/besxy.f9019
-rw-r--r--gcc/testsuite/gfortran.dg/bind_c_usage_9.f0310
-rw-r--r--gcc/testsuite/gfortran.dg/contains_empty_1.f0311
-rw-r--r--gcc/testsuite/gfortran.dg/contains_empty_2.f0314
-rw-r--r--gcc/testsuite/gfortran.dg/derived_function_interface_1.f902
-rw-r--r--gcc/testsuite/gfortran.dg/dg.exp2
-rw-r--r--gcc/testsuite/gfortran.dg/erfc_scaled_1.f9028
-rw-r--r--gcc/testsuite/gfortran.dg/gamma_1.f904
-rw-r--r--gcc/testsuite/gfortran.dg/gamma_2.f908
-rw-r--r--gcc/testsuite/gfortran.dg/gamma_3.f904
-rw-r--r--gcc/testsuite/gfortran.dg/gamma_4.f908
-rw-r--r--gcc/testsuite/gfortran.dg/gomp/gomp.exp2
-rw-r--r--gcc/testsuite/gfortran.dg/hypot_1.f9029
-rw-r--r--gcc/testsuite/gfortran.dg/invalid_contains_1.f902
-rw-r--r--gcc/testsuite/gfortran.dg/invalid_contains_2.f902
-rw-r--r--gcc/testsuite/gfortran.dg/recursive_check_3.f906
-rw-r--r--gcc/testsuite/gfortran.dg/vect/vect.exp10
18 files changed, 167 insertions, 31 deletions
diff --git a/gcc/testsuite/gfortran.dg/bessel_1.f90 b/gcc/testsuite/gfortran.dg/bessel_1.f90
new file mode 100644
index 00000000000..728c5ce49ca
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/bessel_1.f90
@@ -0,0 +1,37 @@
+! { dg-do run }
+
+program test
+ implicit none
+
+ interface check
+ procedure check_r4
+ procedure check_r8
+ end interface check
+
+ real(kind=4) :: x4
+ real(kind=8) :: x8
+
+ x8 = 1.9_8 ; x4 = 1.9_4
+ call check(bessel_j0 (x8), bessel_j0 (1.9_8))
+ call check(bessel_j0 (x4), bessel_j0 (1.9_4))
+ call check(bessel_j1 (x8), bessel_j1 (1.9_8))
+ call check(bessel_j1 (x4), bessel_j1 (1.9_4))
+ call check(bessel_jn (3,x8), bessel_jn (3,1.9_8))
+ call check(bessel_jn (3,x4), bessel_jn (3,1.9_4))
+ call check(bessel_y0 (x8), bessel_y0 (1.9_8))
+ call check(bessel_y0 (x4), bessel_y0 (1.9_4))
+ call check(bessel_y1 (x8), bessel_y1 (1.9_8))
+ call check(bessel_y1 (x4), bessel_y1 (1.9_4))
+ call check(bessel_yn (3,x8), bessel_yn (3,1.9_8))
+ call check(bessel_yn (3,x4), bessel_yn (3,1.9_4))
+
+contains
+ subroutine check_r4 (a, b)
+ real(kind=4), intent(in) :: a, b
+ if (abs(a - b) > 1.e-5 * abs(b)) call abort
+ end subroutine
+ subroutine check_r8 (a, b)
+ real(kind=8), intent(in) :: a, b
+ if (abs(a - b) > 1.e-7 * abs(b)) call abort
+ end subroutine
+end program test
diff --git a/gcc/testsuite/gfortran.dg/besxy.f90 b/gcc/testsuite/gfortran.dg/besxy.f90
index 5b4cbba97f2..5cd5c8a96c7 100644
--- a/gcc/testsuite/gfortran.dg/besxy.f90
+++ b/gcc/testsuite/gfortran.dg/besxy.f90
@@ -21,4 +21,21 @@ PROGRAM test_erf
ra = BESY0(ra)
ra = BESY1(ra)
ra = BESYN(0, ra)
-END PROGRAM \ No newline at end of file
+
+ r = BESSEL_J0(r)
+ r = BESSEL_J1(r)
+ r = BESSEL_JN(0, r)
+
+ r = BESSEL_Y0(r)
+ r = BESSEL_Y1(r)
+ r = BESSEL_YN(0, r)
+
+ ra = BESSEL_J0(ra)
+ ra = BESSEL_J1(ra)
+ ra = BESSEL_JN(0, ra)
+
+ ra = BESSEL_Y0(ra)
+ ra = BESSEL_Y1(ra)
+ ra = BESSEL_YN(0, ra)
+
+END PROGRAM
diff --git a/gcc/testsuite/gfortran.dg/bind_c_usage_9.f03 b/gcc/testsuite/gfortran.dg/bind_c_usage_9.f03
index 0ab782e8c6a..086a1166a16 100644
--- a/gcc/testsuite/gfortran.dg/bind_c_usage_9.f03
+++ b/gcc/testsuite/gfortran.dg/bind_c_usage_9.f03
@@ -9,14 +9,14 @@ subroutine foo() bind(c)
contains
subroutine bar() bind (c) ! { dg-error "may not be specified for an internal" }
end subroutine bar ! { dg-error "Expected label" }
-end subroutine foo ! { dg-warning "Extension: CONTAINS statement" }
+end subroutine foo ! { dg-error "Fortran 2008: CONTAINS statement" }
subroutine foo2() bind(c)
use iso_c_binding
contains
integer(c_int) function barbar() bind (c) ! { dg-error "may not be specified for an internal" }
end function barbar ! { dg-error "Expecting END SUBROUTINE" }
-end subroutine foo2 ! { dg-warning "Extension: CONTAINS statement" }
+end subroutine foo2 ! { dg-error "Fortran 2008: CONTAINS statement" }
function one() bind(c)
use iso_c_binding
@@ -25,7 +25,7 @@ function one() bind(c)
contains
integer(c_int) function two() bind (c) ! { dg-error "may not be specified for an internal" }
end function two ! { dg-error "Expected label" }
-end function one ! { dg-warning "Extension: CONTAINS statement" }
+end function one ! { dg-error "Fortran 2008: CONTAINS statement" }
function one2() bind(c)
use iso_c_binding
@@ -34,7 +34,7 @@ function one2() bind(c)
contains
subroutine three() bind (c) ! { dg-error "may not be specified for an internal" }
end subroutine three ! { dg-error "Expecting END FUNCTION statement" }
-end function one2 ! { dg-warning "Extension: CONTAINS statement" }
+end function one2 ! { dg-error "Fortran 2008: CONTAINS statement" }
program main
use iso_c_binding
@@ -44,4 +44,4 @@ contains
end subroutine test ! { dg-error "Expecting END PROGRAM" }
integer(c_int) function test2() bind (c) ! { dg-error "may not be specified for an internal" }
end function test2 ! { dg-error "Expecting END PROGRAM" }
-end program main ! { dg-warning "Extension: CONTAINS statement" }
+end program main ! { dg-error "Fortran 2008: CONTAINS statement" }
diff --git a/gcc/testsuite/gfortran.dg/contains_empty_1.f03 b/gcc/testsuite/gfortran.dg/contains_empty_1.f03
new file mode 100644
index 00000000000..51b5dd90b16
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/contains_empty_1.f03
@@ -0,0 +1,11 @@
+! { dg-do compile }
+! { dg-options "-std=f2003 -pedantic" }
+program test
+ print *, 'hello there'
+contains
+end program test ! { dg-error "Fortran 2008: CONTAINS statement without" }
+
+module truc
+ integer, parameter :: answer = 42
+contains
+end module truc ! { dg-error "Fortran 2008: CONTAINS statement without" }
diff --git a/gcc/testsuite/gfortran.dg/contains_empty_2.f03 b/gcc/testsuite/gfortran.dg/contains_empty_2.f03
new file mode 100644
index 00000000000..62e18f43d14
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/contains_empty_2.f03
@@ -0,0 +1,14 @@
+! { dg-do compile }
+! { dg-options "-std=f2008 -pedantic" }
+
+program test
+ print *, 'hello there'
+contains
+end program test
+
+module truc
+ integer, parameter :: answer = 42
+contains
+end module truc
+
+! { dg-final { cleanup-modules "truc" } }
diff --git a/gcc/testsuite/gfortran.dg/derived_function_interface_1.f90 b/gcc/testsuite/gfortran.dg/derived_function_interface_1.f90
index a9e404182f6..b7ee4df89a7 100644
--- a/gcc/testsuite/gfortran.dg/derived_function_interface_1.f90
+++ b/gcc/testsuite/gfortran.dg/derived_function_interface_1.f90
@@ -41,5 +41,5 @@ contains
type(foo) function fun() ! { dg-error "already has an explicit interface" }
end function fun ! { dg-error "Expecting END PROGRAM" }
-end ! { dg-warning "CONTAINS statement without FUNCTION or SUBROUTINE statement" }
+end
! { dg-final { cleanup-modules "kinds" } }
diff --git a/gcc/testsuite/gfortran.dg/dg.exp b/gcc/testsuite/gfortran.dg/dg.exp
index a80f6bf1103..2ccdfd0be45 100644
--- a/gcc/testsuite/gfortran.dg/dg.exp
+++ b/gcc/testsuite/gfortran.dg/dg.exp
@@ -30,7 +30,7 @@ dg-init
# Main loop.
gfortran-dg-runtest [lsort \
- [glob -nocomplain $srcdir/$subdir/*.\[fF\]{,90,95,03} ] ] $DEFAULT_FFLAGS
+ [glob -nocomplain $srcdir/$subdir/*.\[fF\]{,90,95,03,08} ] ] $DEFAULT_FFLAGS
gfortran-dg-runtest [lsort \
[glob -nocomplain $srcdir/$subdir/g77/*.\[fF\] ] ] $DEFAULT_FFLAGS
diff --git a/gcc/testsuite/gfortran.dg/erfc_scaled_1.f90 b/gcc/testsuite/gfortran.dg/erfc_scaled_1.f90
new file mode 100644
index 00000000000..8a114e60ef9
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/erfc_scaled_1.f90
@@ -0,0 +1,28 @@
+! { dg-do run }
+
+program test
+ implicit none
+
+ interface check
+ procedure check_r4
+ procedure check_r8
+ end interface check
+
+ real(kind=4) :: x4
+ real(kind=8) :: x8
+
+ x8 = 1.9_8 ; x4 = 1.9_4
+
+ call check(erfc_scaled(x8), erfc_scaled(1.9_8))
+ call check(erfc_scaled(x4), erfc_scaled(1.9_4))
+
+contains
+ subroutine check_r4 (a, b)
+ real(kind=4), intent(in) :: a, b
+ if (abs(a - b) > 1.e-5 * abs(b)) call abort
+ end subroutine
+ subroutine check_r8 (a, b)
+ real(kind=8), intent(in) :: a, b
+ if (abs(a - b) > 1.e-7 * abs(b)) call abort
+ end subroutine
+end program test
diff --git a/gcc/testsuite/gfortran.dg/gamma_1.f90 b/gcc/testsuite/gfortran.dg/gamma_1.f90
index c2bbdb6abf1..9946166952a 100644
--- a/gcc/testsuite/gfortran.dg/gamma_1.f90
+++ b/gcc/testsuite/gfortran.dg/gamma_1.f90
@@ -8,7 +8,7 @@
!
program gamma_test
implicit none
-intrinsic :: gamma, lgamma
+intrinsic :: gamma, lgamma, log_gamma
integer, parameter :: sp = kind(1.0)
integer, parameter :: dp = kind(1.0d0)
@@ -21,6 +21,8 @@ if (abs(dgamma(1.0_dp) - 1.0_dp) > tiny(1.0_dp)) call abort()
if (abs(lgamma(1.0_sp)) > tiny(1.0_sp)) call abort()
if (abs(lgamma(1.0_dp)) > tiny(1.0_dp)) call abort()
+if (abs(log_gamma(1.0_sp)) > tiny(1.0_sp)) call abort()
+if (abs(log_gamma(1.0_dp)) > tiny(1.0_dp)) call abort()
if (abs(algama(1.0_sp)) > tiny(1.0_sp)) call abort()
if (abs(dlgama(1.0_dp)) > tiny(1.0_dp)) call abort()
end program gamma_test
diff --git a/gcc/testsuite/gfortran.dg/gamma_2.f90 b/gcc/testsuite/gfortran.dg/gamma_2.f90
index ca7432b4c5d..6e8cefa6858 100644
--- a/gcc/testsuite/gfortran.dg/gamma_2.f90
+++ b/gcc/testsuite/gfortran.dg/gamma_2.f90
@@ -20,12 +20,12 @@ integer, parameter :: dp = kind(1.0d0)
real(sp) :: rsp = 1.0_sp
real(dp) :: rdp = 1.0_dp
-rsp = gamma(rsp) ! FIXME: "is not included in the selected standard"
-rdp = gamma(rdp) ! FIXME: "is not included in the selected standard"
+rsp = gamma(rsp) ! FIXME "is not included in the selected standard"
+rdp = gamma(rdp) ! FIXME "is not included in the selected standard"
rdp = dgamma(rdp) ! { dg-error "is not included in the selected standard" }
-rsp = lgamma(rsp) ! FIXME: "is not included in the selected standard"
-rdp = lgamma(rdp) ! FIXME: "is not included in the selected standard"
+rsp = lgamma(rsp) ! { dg-error "is not included in the selected standard" }
+rdp = lgamma(rdp) ! { dg-error "is not included in the selected standard" }
rsp = algama(rsp) ! { dg-error "is not included in the selected standard" }
rdp = dlgama(rdp) ! { dg-error "is not included in the selected standard" }
end subroutine foo
diff --git a/gcc/testsuite/gfortran.dg/gamma_3.f90 b/gcc/testsuite/gfortran.dg/gamma_3.f90
index b35596fa5a9..ca3d30db983 100644
--- a/gcc/testsuite/gfortran.dg/gamma_3.f90
+++ b/gcc/testsuite/gfortran.dg/gamma_3.f90
@@ -16,11 +16,11 @@ x = dgamma(cmplx(1.0,0.0,kind(0d0))) ! { dg-error "must be REAL" }
x = gamma(int(1)) ! { dg-error "is not consistent with a specific intrinsic interface" }
x = dgamma(int(1)) ! { dg-error "must be REAL" }
-x = lgamma(cmplx(1.0,0.0)) ! { dg-error "is not consistent with a specific intrinsic interface" }
+x = lgamma(cmplx(1.0,0.0)) ! { dg-error "must be REAL" }
x = algama(cmplx(1.0,0.0)) ! { dg-error "must be REAL" }
x = dlgama(cmplx(1.0,0.0,kind(0d0))) ! { dg-error "must be REAL" }
-x = lgamma(int(1)) ! { dg-error "is not consistent with a specific intrinsic interface" }
+x = lgamma(int(1)) ! { dg-error "must be REAL" }
x = algama(int(1)) ! { dg-error "must be REAL" }
x = dlgama(int(1)) ! { dg-error "must be REAL" }
end program gamma_test
diff --git a/gcc/testsuite/gfortran.dg/gamma_4.f90 b/gcc/testsuite/gfortran.dg/gamma_4.f90
index a351f77958a..67e9e2314a1 100644
--- a/gcc/testsuite/gfortran.dg/gamma_4.f90
+++ b/gcc/testsuite/gfortran.dg/gamma_4.f90
@@ -1,20 +1,18 @@
! { dg-do run }
! { dg-require-effective-target fortran_large_real }
!
-! Test the vendor intrinsic (d)gamma, lgamma and algama/dlgama
-! gamma is also part of the Fortran 2008 draft; lgamma is called
-! log_gamma in the Fortran 2008 draft.
+! Test the Fortran 2008 intrinsics gamma and log_gamma
!
! PR fortran/32980
!
program gamma_test
implicit none
-intrinsic :: gamma, lgamma
+intrinsic :: gamma, log_gamma
integer, parameter :: qp = selected_real_kind(precision (0.0_8) + 1)
real(qp) :: rqp
if (abs(gamma(1.0_qp) - 1.0_qp) > tiny(1.0_qp)) call abort()
-if (abs(lgamma(1.0_qp)) > tiny(1.0_qp)) call abort()
+if (abs(log_gamma(1.0_qp)) > tiny(1.0_qp)) call abort()
end program gamma_test
diff --git a/gcc/testsuite/gfortran.dg/gomp/gomp.exp b/gcc/testsuite/gfortran.dg/gomp/gomp.exp
index 185bc3da596..34ae1466ed0 100644
--- a/gcc/testsuite/gfortran.dg/gomp/gomp.exp
+++ b/gcc/testsuite/gfortran.dg/gomp/gomp.exp
@@ -12,7 +12,7 @@ dg-init
# Main loop.
gfortran-dg-runtest [lsort \
- [find $srcdir/$subdir *.\[fF\]{,90,95,03} ] ] " -fopenmp"
+ [find $srcdir/$subdir *.\[fF\]{,90,95,03,08} ] ] " -fopenmp"
# All done.
dg-finish
diff --git a/gcc/testsuite/gfortran.dg/hypot_1.f90 b/gcc/testsuite/gfortran.dg/hypot_1.f90
new file mode 100644
index 00000000000..59022fab93c
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/hypot_1.f90
@@ -0,0 +1,29 @@
+! { dg-do run }
+
+program test
+ implicit none
+
+ interface check
+ procedure check_r4
+ procedure check_r8
+ end interface check
+
+ real(kind=4) :: x4, y4
+ real(kind=8) :: x8, y8
+
+ x8 = 1.9_8 ; x4 = 1.9_4
+ y8 = -2.1_8 ; y4 = -2.1_4
+
+ call check(hypot(x8,y8), hypot(1.9_8,-2.1_8))
+ call check(hypot(x4,y4), hypot(1.9_4,-2.1_4))
+
+contains
+ subroutine check_r4 (a, b)
+ real(kind=4), intent(in) :: a, b
+ if (abs(a - b) > 1.e-5 * abs(b)) call abort
+ end subroutine
+ subroutine check_r8 (a, b)
+ real(kind=8), intent(in) :: a, b
+ if (abs(a - b) > 1.e-7 * abs(b)) call abort
+ end subroutine
+end program test
diff --git a/gcc/testsuite/gfortran.dg/invalid_contains_1.f90 b/gcc/testsuite/gfortran.dg/invalid_contains_1.f90
index 757751d2427..df4bb3fef2d 100644
--- a/gcc/testsuite/gfortran.dg/invalid_contains_1.f90
+++ b/gcc/testsuite/gfortran.dg/invalid_contains_1.f90
@@ -5,4 +5,4 @@ contains
subroutine FOO ! { dg-error "conflicts with PROCEDURE" }
character(len=selected_int_kind(0)) :: C ! { dg-error "data declaration statement" }
end subroutine ! { dg-error "Expecting END MODULE statement" }
-end ! { dg-warning "CONTAINS statement without FUNCTION" } \ No newline at end of file
+end
diff --git a/gcc/testsuite/gfortran.dg/invalid_contains_2.f90 b/gcc/testsuite/gfortran.dg/invalid_contains_2.f90
index 90be10fd06d..72c1e216f07 100644
--- a/gcc/testsuite/gfortran.dg/invalid_contains_2.f90
+++ b/gcc/testsuite/gfortran.dg/invalid_contains_2.f90
@@ -6,4 +6,4 @@ contains
integer :: i ! { dg-error "data declaration statement" }
character(len=selected_int_kind(i)) :: c ! { dg-error "data declaration statement" }
end subroutine ! { dg-error "Expecting END PROGRAM statement" }
-end program foo ! { dg-warning "CONTAINS statement without FUNCTION" }
+end program foo
diff --git a/gcc/testsuite/gfortran.dg/recursive_check_3.f90 b/gcc/testsuite/gfortran.dg/recursive_check_3.f90
index 23904a8b991..ec358cb12c0 100644
--- a/gcc/testsuite/gfortran.dg/recursive_check_3.f90
+++ b/gcc/testsuite/gfortran.dg/recursive_check_3.f90
@@ -5,18 +5,18 @@ contains
pure pure subroutine a1(b) ! { dg-error "Duplicate PURE attribute specified" }
real, intent(in) :: b ! { dg-error "Unexpected data declaration statement" }
end subroutine a1 ! { dg-error "Expecting END MODULE" }
-end module m1 ! { dg-warning "CONTAINS statement without FUNCTION" }
+end module m1
module m2
contains
elemental elemental subroutine a2(b) ! { dg-error "Duplicate ELEMENTAL attribute" }
real, intent(in) :: b ! { dg-error "Unexpected data declaration statement" }
end subroutine a2 ! { dg-error "Expecting END MODULE" }
-end module m2 ! { dg-warning "CONTAINS statement without FUNCTION" }
+end module m2
module m3
contains
recursive recursive subroutine a3(b) ! { dg-error "Duplicate RECURSIVE attribute" }
real, intent(in) :: b ! { dg-error "Unexpected data declaration statement" }
end subroutine a3 ! { dg-error "Expecting END MODULE" }
-end module m3 ! { dg-warning "CONTAINS statement without FUNCTION" }
+end module m3
diff --git a/gcc/testsuite/gfortran.dg/vect/vect.exp b/gcc/testsuite/gfortran.dg/vect/vect.exp
index a1b949899fc..9f91434a702 100644
--- a/gcc/testsuite/gfortran.dg/vect/vect.exp
+++ b/gcc/testsuite/gfortran.dg/vect/vect.exp
@@ -90,8 +90,8 @@ proc check_effective_target_lp64_or_vect_no_align { } {
dg-init
# Main loop.
-gfortran-dg-runtest [lsort [glob -nocomplain $srcdir/$subdir/vect-*.\[fF\]{,90,95,03} ]] $DEFAULT_VECTCFLAGS
-gfortran-dg-runtest [lsort [glob -nocomplain $srcdir/$subdir/pr*.\[fF\]{,90,95,03} ]] $DEFAULT_VECTCFLAGS
+gfortran-dg-runtest [lsort [glob -nocomplain $srcdir/$subdir/vect-*.\[fF\]{,90,95,03,08} ]] $DEFAULT_VECTCFLAGS
+gfortran-dg-runtest [lsort [glob -nocomplain $srcdir/$subdir/pr*.\[fF\]{,90,95,03,08} ]] $DEFAULT_VECTCFLAGS
#### Tests with special options
global SAVED_DEFAULT_VECTCFLAGS
@@ -100,19 +100,19 @@ set SAVED_DEFAULT_VECTCFLAGS $DEFAULT_VECTCFLAGS
# -ffast-math tests
set DEFAULT_VECTCFLAGS $SAVED_DEFAULT_VECTCFLAGS
lappend DEFAULT_VECTCFLAGS "-ffast-math"
-dg-runtest [lsort [glob -nocomplain $srcdir/$subdir/fast-math-*.\[fF\]{,90,95,03} ]] \
+dg-runtest [lsort [glob -nocomplain $srcdir/$subdir/fast-math-*.\[fF\]{,90,95,03,08} ]] \
"" $DEFAULT_VECTCFLAGS
# -fvect-cost-model tests
set DEFAULT_VECTCFLAGS $SAVED_DEFAULT_VECTCFLAGS
lappend DEFAULT_VECTCFLAGS "-fvect-cost-model"
-dg-runtest [lsort [glob -nocomplain $srcdir/$subdir/cost-model-*.\[fF\]{,90,95,03} ]] \
+dg-runtest [lsort [glob -nocomplain $srcdir/$subdir/cost-model-*.\[fF\]{,90,95,03,08} ]] \
"" $DEFAULT_VECTCFLAGS
# --param vect-max-version-for-alias-checks=0 tests
set DEFAULT_VECTCFLAGS $SAVED_DEFAULT_VECTCFLAGS
lappend DEFAULT_VECTCFLAGS "--param" "vect-max-version-for-alias-checks=0"
-dg-runtest [lsort [glob -nocomplain $srcdir/$subdir/no-vfa-*.\[fF\]{,90,95,03} ]] \
+dg-runtest [lsort [glob -nocomplain $srcdir/$subdir/no-vfa-*.\[fF\]{,90,95,03,08} ]] \
"" $DEFAULT_VECTCFLAGS
# Clean up.