diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog index 7fc8f0eef5eb..9980ad7e2944 100644 --- a/gcc/testsuite/ChangeLog +++ b/gcc/testsuite/ChangeLog @@ -1,3 +1,8 @@ +2012-05-15 Bernhard Reutner-Fischer + + * gfortran.dg/*.f90: Remove now redundant manual + cleanup-modules directive. + 2012-05-14 Uros Bizjak * gcc.target/i386/avx256-unaligned-load-[1234].c: Update scan strings. diff --git a/gcc/testsuite/gfortran.dg/abstract_type_1.f90 b/gcc/testsuite/gfortran.dg/abstract_type_1.f90 index d0cd4320a7cd..09757b1f9295 100644 --- a/gcc/testsuite/gfortran.dg/abstract_type_1.f90 +++ b/gcc/testsuite/gfortran.dg/abstract_type_1.f90 @@ -11,4 +11,3 @@ MODULE m END TYPE t ! { dg-error "END MODULE" } END MODULE m -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/abstract_type_2.f03 b/gcc/testsuite/gfortran.dg/abstract_type_2.f03 index 2583f1f4f801..b261ce2fe134 100644 --- a/gcc/testsuite/gfortran.dg/abstract_type_2.f03 +++ b/gcc/testsuite/gfortran.dg/abstract_type_2.f03 @@ -11,4 +11,3 @@ MODULE m END TYPE error_t ! { dg-error "END MODULE" } END MODULE m -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/abstract_type_3.f03 b/gcc/testsuite/gfortran.dg/abstract_type_3.f03 index 79bc131e0c64..e7a9d9b63577 100644 --- a/gcc/testsuite/gfortran.dg/abstract_type_3.f03 +++ b/gcc/testsuite/gfortran.dg/abstract_type_3.f03 @@ -49,4 +49,3 @@ CONTAINS END SUBROUTINE impl END MODULE m -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/abstract_type_4.f03 b/gcc/testsuite/gfortran.dg/abstract_type_4.f03 index a6e5de208828..dd0b0abc0710 100644 --- a/gcc/testsuite/gfortran.dg/abstract_type_4.f03 +++ b/gcc/testsuite/gfortran.dg/abstract_type_4.f03 @@ -26,4 +26,3 @@ PROGRAM main ! See if constructing the extending type works. conc = concrete_t (1, 2) END PROGRAM main -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/abstract_type_5.f03 b/gcc/testsuite/gfortran.dg/abstract_type_5.f03 index 42ac963face7..6e72882cfeaa 100644 --- a/gcc/testsuite/gfortran.dg/abstract_type_5.f03 +++ b/gcc/testsuite/gfortran.dg/abstract_type_5.f03 @@ -43,4 +43,3 @@ CONTAINS END SUBROUTINE test END MODULE m -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/abstract_type_6.f03 b/gcc/testsuite/gfortran.dg/abstract_type_6.f03 index de1cea363233..e4abd793288e 100644 --- a/gcc/testsuite/gfortran.dg/abstract_type_6.f03 +++ b/gcc/testsuite/gfortran.dg/abstract_type_6.f03 @@ -50,4 +50,3 @@ SUBROUTINE bottom_c(obj) ! other stuff END SUBROUTINE bottom_c end module -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/abstract_type_7.f03 b/gcc/testsuite/gfortran.dg/abstract_type_7.f03 index 3ea0fdca6147..382cf9e7951d 100644 --- a/gcc/testsuite/gfortran.dg/abstract_type_7.f03 +++ b/gcc/testsuite/gfortran.dg/abstract_type_7.f03 @@ -15,4 +15,3 @@ module ice_module end type c_type end module ice_module -! { dg-final { cleanup-modules "ice_module" } } diff --git a/gcc/testsuite/gfortran.dg/abstract_type_8.f03 b/gcc/testsuite/gfortran.dg/abstract_type_8.f03 index c924abac9af4..edcb37a6e110 100644 --- a/gcc/testsuite/gfortran.dg/abstract_type_8.f03 +++ b/gcc/testsuite/gfortran.dg/abstract_type_8.f03 @@ -25,5 +25,3 @@ abstract interface end subroutine generic_desc end interface end module factory_pattern - -! { dg-final { cleanup-modules "factory_pattern" } } diff --git a/gcc/testsuite/gfortran.dg/access_spec_1.f90 b/gcc/testsuite/gfortran.dg/access_spec_1.f90 index 2c080c9c62fd..8bebd1131308 100644 --- a/gcc/testsuite/gfortran.dg/access_spec_1.f90 +++ b/gcc/testsuite/gfortran.dg/access_spec_1.f90 @@ -15,4 +15,3 @@ module mod integer, private :: z ! Fortran 2003 end type end module -! { dg-final { cleanup-modules "mod" } } diff --git a/gcc/testsuite/gfortran.dg/access_spec_2.f90 b/gcc/testsuite/gfortran.dg/access_spec_2.f90 index 7b67e6c85979..ccb56e2cdc23 100644 --- a/gcc/testsuite/gfortran.dg/access_spec_2.f90 +++ b/gcc/testsuite/gfortran.dg/access_spec_2.f90 @@ -37,4 +37,3 @@ program x public :: i ! { dg-error "only allowed in the specification part of a module" } integer,public :: j ! { dg-error "not allowed outside of the specification part of a module" } end program x -! { dg-final { cleanup-modules "test mod" } } diff --git a/gcc/testsuite/gfortran.dg/access_spec_3.f90 b/gcc/testsuite/gfortran.dg/access_spec_3.f90 index 9a076b66c546..838b47b2f4b8 100644 --- a/gcc/testsuite/gfortran.dg/access_spec_3.f90 +++ b/gcc/testsuite/gfortran.dg/access_spec_3.f90 @@ -31,4 +31,3 @@ program user bint = 8 write(*,*) aint end program -! { dg-final { cleanup-modules "base a b c" } } diff --git a/gcc/testsuite/gfortran.dg/actual_array_constructor_1.f90 b/gcc/testsuite/gfortran.dg/actual_array_constructor_1.f90 index 69bfcd05a530..1caf6522128a 100644 --- a/gcc/testsuite/gfortran.dg/actual_array_constructor_1.f90 +++ b/gcc/testsuite/gfortran.dg/actual_array_constructor_1.f90 @@ -78,5 +78,3 @@ contains end subroutine option_stopwatch_a end program main -! { dg-final { cleanup-modules "global my_module" } } - diff --git a/gcc/testsuite/gfortran.dg/actual_array_result_1.f90 b/gcc/testsuite/gfortran.dg/actual_array_result_1.f90 index cf79315cbb72..04c7e679b10f 100644 --- a/gcc/testsuite/gfortran.dg/actual_array_result_1.f90 +++ b/gcc/testsuite/gfortran.dg/actual_array_result_1.f90 @@ -68,4 +68,3 @@ program main n = 5 if(any (foo3(n) /= [ 0,1,2,3,0 ])) call abort() end program -! { dg-final { cleanup-modules "one" } } diff --git a/gcc/testsuite/gfortran.dg/actual_array_vect_1.f90 b/gcc/testsuite/gfortran.dg/actual_array_vect_1.f90 index cbee22676a2b..8b4d6f495198 100644 --- a/gcc/testsuite/gfortran.dg/actual_array_vect_1.f90 +++ b/gcc/testsuite/gfortran.dg/actual_array_vect_1.f90 @@ -31,5 +31,3 @@ call bb(w(2:4)) call bb(w((/3,2,1/))) ! { dg-error "vector subscript" } write(*,*)w end - -! { dg-final { cleanup-modules "mod" } } diff --git a/gcc/testsuite/gfortran.dg/actual_procedure_1.f90 b/gcc/testsuite/gfortran.dg/actual_procedure_1.f90 index 5327cb73d7f5..4a7f3d81180a 100644 --- a/gcc/testsuite/gfortran.dg/actual_procedure_1.f90 +++ b/gcc/testsuite/gfortran.dg/actual_procedure_1.f90 @@ -69,4 +69,3 @@ function proc_ext (arg, chr) proc_ext = arg chr = "proc_ext" end function -! { dg-final { cleanup-modules "m" } } \ No newline at end of file diff --git a/gcc/testsuite/gfortran.dg/aliasing_array_result_1.f90 b/gcc/testsuite/gfortran.dg/aliasing_array_result_1.f90 index d8899d2ecf87..ddfba012ae63 100644 --- a/gcc/testsuite/gfortran.dg/aliasing_array_result_1.f90 +++ b/gcc/testsuite/gfortran.dg/aliasing_array_result_1.f90 @@ -161,4 +161,3 @@ contains get_d = d end function get_d end program test -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/aliasing_dummy_5.f90 b/gcc/testsuite/gfortran.dg/aliasing_dummy_5.f90 index 379fbd7f8f9d..cc52456f0d9e 100644 --- a/gcc/testsuite/gfortran.dg/aliasing_dummy_5.f90 +++ b/gcc/testsuite/gfortran.dg/aliasing_dummy_5.f90 @@ -51,5 +51,3 @@ contains CALL foobar (x) end subroutine bar END subroutine test - -! { dg-final { cleanup-modules "m m2" } } diff --git a/gcc/testsuite/gfortran.dg/alloc_alloc_expr_3.f90 b/gcc/testsuite/gfortran.dg/alloc_alloc_expr_3.f90 index 13b2230c0ab7..e7a5ff21cf66 100644 --- a/gcc/testsuite/gfortran.dg/alloc_alloc_expr_3.f90 +++ b/gcc/testsuite/gfortran.dg/alloc_alloc_expr_3.f90 @@ -21,5 +21,3 @@ function func2() end function end module foo - -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/alloc_comp_assign_10.f90 b/gcc/testsuite/gfortran.dg/alloc_comp_assign_10.f90 index c85edea62fc9..808a2898cfa2 100644 --- a/gcc/testsuite/gfortran.dg/alloc_comp_assign_10.f90 +++ b/gcc/testsuite/gfortran.dg/alloc_comp_assign_10.f90 @@ -57,5 +57,3 @@ program tao_program deallocate (u%design, u%model) deallocate (s%u) end program - -! { dg-final { cleanup-modules "test_struct" } } diff --git a/gcc/testsuite/gfortran.dg/alloc_comp_assign_12.f03 b/gcc/testsuite/gfortran.dg/alloc_comp_assign_12.f03 index b44769d9668f..ea8067d389c9 100644 --- a/gcc/testsuite/gfortran.dg/alloc_comp_assign_12.f03 +++ b/gcc/testsuite/gfortran.dg/alloc_comp_assign_12.f03 @@ -40,5 +40,3 @@ program main2 call o%make(u) if (any (int (o%disp()) .ne. [1,2])) call abort end program main2 -! { dg-final { cleanup-modules "foo" } } - diff --git a/gcc/testsuite/gfortran.dg/alloc_comp_assign_6.f90 b/gcc/testsuite/gfortran.dg/alloc_comp_assign_6.f90 index 4e8edc228727..c3882761f958 100644 --- a/gcc/testsuite/gfortran.dg/alloc_comp_assign_6.f90 +++ b/gcc/testsuite/gfortran.dg/alloc_comp_assign_6.f90 @@ -51,5 +51,3 @@ program VST28 call abort () end if end program VST28 - -! { dg-final { cleanup-modules "iso_varying_string" } } diff --git a/gcc/testsuite/gfortran.dg/alloc_comp_assign_7.f90 b/gcc/testsuite/gfortran.dg/alloc_comp_assign_7.f90 index c7e9b757d778..08e98c2c3325 100644 --- a/gcc/testsuite/gfortran.dg/alloc_comp_assign_7.f90 +++ b/gcc/testsuite/gfortran.dg/alloc_comp_assign_7.f90 @@ -36,5 +36,3 @@ end module PrettyPix_module if (this%look_at_path%r(i)%y2(1) .ne. x(i)) call abort end do end - -! { dg-final { cleanup-modules "prettypix_module" } } diff --git a/gcc/testsuite/gfortran.dg/alloc_comp_assign_8.f90 b/gcc/testsuite/gfortran.dg/alloc_comp_assign_8.f90 index ab4868de1367..655ef856ba89 100644 --- a/gcc/testsuite/gfortran.dg/alloc_comp_assign_8.f90 +++ b/gcc/testsuite/gfortran.dg/alloc_comp_assign_8.f90 @@ -46,5 +46,3 @@ end module if (t1%a .ne. -0.5d0) call abort if (any(t1%b .ne. [-1d0, -2d0])) call abort end - -! { dg-final { cleanup-modules "typemodule" } } diff --git a/gcc/testsuite/gfortran.dg/alloc_comp_auto_array_2.f90 b/gcc/testsuite/gfortran.dg/alloc_comp_auto_array_2.f90 index c8945cfc3751..c4c4ae21e01c 100644 --- a/gcc/testsuite/gfortran.dg/alloc_comp_auto_array_2.f90 +++ b/gcc/testsuite/gfortran.dg/alloc_comp_auto_array_2.f90 @@ -38,4 +38,3 @@ end module grid_io call read_grid_header end ! { dg-final { cleanup-tree-dump "grid_io" } } -! { dg-final { cleanup-modules "grid_io" } } diff --git a/gcc/testsuite/gfortran.dg/alloc_comp_basics_1.f90 b/gcc/testsuite/gfortran.dg/alloc_comp_basics_1.f90 index e53112ce46e0..9b08129add62 100644 --- a/gcc/testsuite/gfortran.dg/alloc_comp_basics_1.f90 +++ b/gcc/testsuite/gfortran.dg/alloc_comp_basics_1.f90 @@ -141,4 +141,3 @@ contains end program alloc ! { dg-final { scan-tree-dump-times "builtin_free" 18 "original" } } ! { dg-final { cleanup-tree-dump "original" } } -! { dg-final { cleanup-modules "alloc_m" } } diff --git a/gcc/testsuite/gfortran.dg/alloc_comp_basics_4.f90 b/gcc/testsuite/gfortran.dg/alloc_comp_basics_4.f90 index 508d5670689f..9877d3b7ec14 100644 --- a/gcc/testsuite/gfortran.dg/alloc_comp_basics_4.f90 +++ b/gcc/testsuite/gfortran.dg/alloc_comp_basics_4.f90 @@ -21,5 +21,3 @@ MODULE globals_m USE types_m TYPE(grib_t) g_dest ! output field END MODULE -! { dg-final { cleanup-modules "types_m globals_m" } } - diff --git a/gcc/testsuite/gfortran.dg/alloc_comp_basics_5.f90 b/gcc/testsuite/gfortran.dg/alloc_comp_basics_5.f90 index 99cd9e08ce34..9dd4e97f5bb2 100644 --- a/gcc/testsuite/gfortran.dg/alloc_comp_basics_5.f90 +++ b/gcc/testsuite/gfortran.dg/alloc_comp_basics_5.f90 @@ -43,5 +43,3 @@ program tsave if (info .ne. 10) call abort () end program tsave - -! { dg-final { cleanup-modules "bar_mod" } } diff --git a/gcc/testsuite/gfortran.dg/alloc_comp_class_1.f90 b/gcc/testsuite/gfortran.dg/alloc_comp_class_1.f90 index c783f49ff77f..8add2c7f4861 100644 --- a/gcc/testsuite/gfortran.dg/alloc_comp_class_1.f90 +++ b/gcc/testsuite/gfortran.dg/alloc_comp_class_1.f90 @@ -30,4 +30,3 @@ contains type(d_sparse_mat), intent(out) :: a end subroutine bug14 end -! { dg-final { cleanup-modules "d_mat_mod " } } diff --git a/gcc/testsuite/gfortran.dg/alloc_comp_constraint_6.f90 b/gcc/testsuite/gfortran.dg/alloc_comp_constraint_6.f90 index e2b609aee5a2..787f30a609a6 100644 --- a/gcc/testsuite/gfortran.dg/alloc_comp_constraint_6.f90 +++ b/gcc/testsuite/gfortran.dg/alloc_comp_constraint_6.f90 @@ -18,4 +18,3 @@ module cell return end subroutine cell_output end module cell -! { dg-final { cleanup-modules "cell" } } diff --git a/gcc/testsuite/gfortran.dg/alloc_comp_initializer_1.f90 b/gcc/testsuite/gfortran.dg/alloc_comp_initializer_1.f90 index 1976509aaaec..ac37fd6e3897 100644 --- a/gcc/testsuite/gfortran.dg/alloc_comp_initializer_1.f90 +++ b/gcc/testsuite/gfortran.dg/alloc_comp_initializer_1.f90 @@ -68,4 +68,3 @@ contains end subroutine p_bld end program foo -! { dg-final { cleanup-modules "p_type_mod" } } diff --git a/gcc/testsuite/gfortran.dg/alloc_comp_result_1.f90 b/gcc/testsuite/gfortran.dg/alloc_comp_result_1.f90 index 90f6d97fdf96..34f25c0ed615 100644 --- a/gcc/testsuite/gfortran.dg/alloc_comp_result_1.f90 +++ b/gcc/testsuite/gfortran.dg/alloc_comp_result_1.f90 @@ -30,4 +30,3 @@ program test x = a_fun(0) if (any (x(1)%mons%coeff .ne. 99)) call abort end program test -! { dg-final { cleanup-modules "mod_a" } } diff --git a/gcc/testsuite/gfortran.dg/allocatable_function_1.f90 b/gcc/testsuite/gfortran.dg/allocatable_function_1.f90 index fc3b983ad1d4..05e0be069f47 100644 --- a/gcc/testsuite/gfortran.dg/allocatable_function_1.f90 +++ b/gcc/testsuite/gfortran.dg/allocatable_function_1.f90 @@ -109,4 +109,3 @@ contains end program alloc_fun ! { dg-final { scan-tree-dump-times "free" 10 "original" } } ! { dg-final { cleanup-tree-dump "original" } } -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/allocatable_function_5.f90 b/gcc/testsuite/gfortran.dg/allocatable_function_5.f90 index 087100cafd0f..8e7d49b0fa88 100644 --- a/gcc/testsuite/gfortran.dg/allocatable_function_5.f90 +++ b/gcc/testsuite/gfortran.dg/allocatable_function_5.f90 @@ -46,5 +46,3 @@ contains bar = carg(1:12) end function end - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/allocatable_module_1.f90 b/gcc/testsuite/gfortran.dg/allocatable_module_1.f90 index 47f10008efab..36671fee2b11 100644 --- a/gcc/testsuite/gfortran.dg/allocatable_module_1.f90 +++ b/gcc/testsuite/gfortran.dg/allocatable_module_1.f90 @@ -15,4 +15,3 @@ program fred use fred1 use fred2 end program fred -! { dg-final { cleanup-modules "fred1 fred2" } } diff --git a/gcc/testsuite/gfortran.dg/allocatable_scalar_9.f90 b/gcc/testsuite/gfortran.dg/allocatable_scalar_9.f90 index f4c6599b02c4..3488c0d72779 100644 --- a/gcc/testsuite/gfortran.dg/allocatable_scalar_9.f90 +++ b/gcc/testsuite/gfortran.dg/allocatable_scalar_9.f90 @@ -51,5 +51,3 @@ end ! { dg-final { scan-tree-dump-times "__builtin_free" 32 "original" } } ! { dg-final { cleanup-tree-dump "original" } } - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/allocate_char_star_scalar_1.f90 b/gcc/testsuite/gfortran.dg/allocate_char_star_scalar_1.f90 index 7e6d7d1f0d25..305136cd6594 100644 --- a/gcc/testsuite/gfortran.dg/allocate_char_star_scalar_1.f90 +++ b/gcc/testsuite/gfortran.dg/allocate_char_star_scalar_1.f90 @@ -29,5 +29,3 @@ program hum call foo(q) end program hum - -! { dg-final { cleanup-modules "moo" } } diff --git a/gcc/testsuite/gfortran.dg/allocate_stat.f90 b/gcc/testsuite/gfortran.dg/allocate_stat.f90 index ceddc925386b..7f9eaf58d6d0 100644 --- a/gcc/testsuite/gfortran.dg/allocate_stat.f90 +++ b/gcc/testsuite/gfortran.dg/allocate_stat.f90 @@ -74,4 +74,3 @@ contains if(associated(p)) deallocate(p) end subroutine sub end module test -! { dg-final { cleanup-modules "test" } } diff --git a/gcc/testsuite/gfortran.dg/allocate_with_source_1.f90 b/gcc/testsuite/gfortran.dg/allocate_with_source_1.f90 index d386bb33b7c9..0069092f6b8b 100644 --- a/gcc/testsuite/gfortran.dg/allocate_with_source_1.f90 +++ b/gcc/testsuite/gfortran.dg/allocate_with_source_1.f90 @@ -26,4 +26,3 @@ program note7_35 if (name .ne. 'xxxxxxxxxx') call abort if (len (name) .ne. 10 ) call abort end program note7_35 -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/altreturn_3.f90 b/gcc/testsuite/gfortran.dg/altreturn_3.f90 index daa09017859b..28fc6a8aa8a1 100644 --- a/gcc/testsuite/gfortran.dg/altreturn_3.f90 +++ b/gcc/testsuite/gfortran.dg/altreturn_3.f90 @@ -42,4 +42,3 @@ program test 20 continue if (i /= -1) call abort () end -! { dg-final { cleanup-modules "arswitch" } } diff --git a/gcc/testsuite/gfortran.dg/altreturn_7.f90 b/gcc/testsuite/gfortran.dg/altreturn_7.f90 index d1786d038c8c..e667ff436c3f 100644 --- a/gcc/testsuite/gfortran.dg/altreturn_7.f90 +++ b/gcc/testsuite/gfortran.dg/altreturn_7.f90 @@ -30,6 +30,3 @@ END MODULE CALL ABORT() 2 CONTINUE END - -! { dg-final { cleanup-modules "tt" } } - diff --git a/gcc/testsuite/gfortran.dg/ambiguous_reference_1.f90 b/gcc/testsuite/gfortran.dg/ambiguous_reference_1.f90 index 93b155ef56df..552118fd4f72 100644 --- a/gcc/testsuite/gfortran.dg/ambiguous_reference_1.f90 +++ b/gcc/testsuite/gfortran.dg/ambiguous_reference_1.f90 @@ -47,4 +47,3 @@ end program test function x(z) x = z end function x -! { dg-final { cleanup-modules "m1 m2 m3 m4 m5 m6" } } diff --git a/gcc/testsuite/gfortran.dg/ambiguous_reference_2.f90 b/gcc/testsuite/gfortran.dg/ambiguous_reference_2.f90 index 3ffaa14591db..bb29d84937aa 100644 --- a/gcc/testsuite/gfortran.dg/ambiguous_reference_2.f90 +++ b/gcc/testsuite/gfortran.dg/ambiguous_reference_2.f90 @@ -28,6 +28,3 @@ contains end subroutine myRoutine ! this is not ambiguous ! end module - -! { dg-final { cleanup-modules "a1 a2 b" } } - diff --git a/gcc/testsuite/gfortran.dg/ambiguous_specific_1.f90 b/gcc/testsuite/gfortran.dg/ambiguous_specific_1.f90 index b5292b2dd825..1097b9f3cbf4 100644 --- a/gcc/testsuite/gfortran.dg/ambiguous_specific_1.f90 +++ b/gcc/testsuite/gfortran.dg/ambiguous_specific_1.f90 @@ -35,4 +35,3 @@ PROGRAM P CALL FOO(10.) call bar (foo) ! { dg-error "is ambiguous" } END PROGRAM P -! { dg-final { cleanup-modules "m1 m2" } } diff --git a/gcc/testsuite/gfortran.dg/ambiguous_specific_2.f90 b/gcc/testsuite/gfortran.dg/ambiguous_specific_2.f90 index 4597b3c86303..79385db8c086 100644 --- a/gcc/testsuite/gfortran.dg/ambiguous_specific_2.f90 +++ b/gcc/testsuite/gfortran.dg/ambiguous_specific_2.f90 @@ -39,4 +39,3 @@ END PROGRAM P SUBROUTINE bar (arg) EXTERNAL arg END SUBROUTINE bar -! { dg-final { cleanup-modules "m1 m2" } } diff --git a/gcc/testsuite/gfortran.dg/argument_checking_17.f90 b/gcc/testsuite/gfortran.dg/argument_checking_17.f90 index df8296ba511c..0921a12de7cf 100644 --- a/gcc/testsuite/gfortran.dg/argument_checking_17.f90 +++ b/gcc/testsuite/gfortran.dg/argument_checking_17.f90 @@ -22,5 +22,3 @@ contains call sub2(a%mdr(GRH_SIZE+1),a%size-GRH_SIZE) end subroutine sub1 end module teststr - -! { dg-final { cleanup-modules "teststr" } } diff --git a/gcc/testsuite/gfortran.dg/argument_checking_8.f90 b/gcc/testsuite/gfortran.dg/argument_checking_8.f90 index 05c94f625fae..fd1daa64f9e2 100644 --- a/gcc/testsuite/gfortran.dg/argument_checking_8.f90 +++ b/gcc/testsuite/gfortran.dg/argument_checking_8.f90 @@ -26,4 +26,3 @@ program test if (astr(i:i) /= achar(0)) call abort end do end program test -! { dg-final { cleanup-modules "cyclic" } } diff --git a/gcc/testsuite/gfortran.dg/array_constructor_20.f90 b/gcc/testsuite/gfortran.dg/array_constructor_20.f90 index 2908edb66e21..32a05a667efb 100644 --- a/gcc/testsuite/gfortran.dg/array_constructor_20.f90 +++ b/gcc/testsuite/gfortran.dg/array_constructor_20.f90 @@ -18,5 +18,3 @@ CONTAINS if (present (j1)) stop end subroutine END MODULE s_TESTS - -! { dg-final { cleanup-modules "m s_tests" } } diff --git a/gcc/testsuite/gfortran.dg/array_constructor_21.f90 b/gcc/testsuite/gfortran.dg/array_constructor_21.f90 index e24b146f3818..1b92c4ea1f6d 100644 --- a/gcc/testsuite/gfortran.dg/array_constructor_21.f90 +++ b/gcc/testsuite/gfortran.dg/array_constructor_21.f90 @@ -33,4 +33,3 @@ UDS0L = SEQ(RESHAPE ( (/ ((CA_T(J1,J2), J1 = 1, 1), J2 = 1, 2)/),(/2/))) END SUBROUTINE END -! { dg-final { cleanup-modules "o_type_defs tests" } } diff --git a/gcc/testsuite/gfortran.dg/array_constructor_22.f90 b/gcc/testsuite/gfortran.dg/array_constructor_22.f90 index 4744dcd3137d..0dcdaea68c1a 100644 --- a/gcc/testsuite/gfortran.dg/array_constructor_22.f90 +++ b/gcc/testsuite/gfortran.dg/array_constructor_22.f90 @@ -25,4 +25,3 @@ program len_test write(*,*) my_string(x) end program len_test -! { dg-final { cleanup-modules "test" } } diff --git a/gcc/testsuite/gfortran.dg/array_constructor_26.f03 b/gcc/testsuite/gfortran.dg/array_constructor_26.f03 index 18c08c486b3e..ac5dc90cc8cb 100644 --- a/gcc/testsuite/gfortran.dg/array_constructor_26.f03 +++ b/gcc/testsuite/gfortran.dg/array_constructor_26.f03 @@ -15,5 +15,3 @@ MODULE WinData ! { dg-error "specification expression" "" { target *-*-* } 13 } END TYPE TWindowData END MODULE WinData - -! { dg-final { cleanup-modules "windata" } } diff --git a/gcc/testsuite/gfortran.dg/array_function_3.f90 b/gcc/testsuite/gfortran.dg/array_function_3.f90 index b1a9cac4400a..3d0ee91176b4 100644 --- a/gcc/testsuite/gfortran.dg/array_function_3.f90 +++ b/gcc/testsuite/gfortran.dg/array_function_3.f90 @@ -44,5 +44,3 @@ ubound(overlap_1(vorticityMag,lbound(vorticityMag),ubound(vorticityMag)),3))) return end subroutine write_out_particles - -! { dg-final { cleanup-modules "communication_tools" } } diff --git a/gcc/testsuite/gfortran.dg/array_function_4.f90 b/gcc/testsuite/gfortran.dg/array_function_4.f90 index 20cb2d588458..f98b545518cd 100644 --- a/gcc/testsuite/gfortran.dg/array_function_4.f90 +++ b/gcc/testsuite/gfortran.dg/array_function_4.f90 @@ -25,5 +25,3 @@ CONTAINS lenf = x(1) end function lenf END MODULE B1 - -! { dg-final { cleanup-modules "b1" } } diff --git a/gcc/testsuite/gfortran.dg/array_memset_2.f90 b/gcc/testsuite/gfortran.dg/array_memset_2.f90 index 7805f7b9420f..28c15ae59ad8 100644 --- a/gcc/testsuite/gfortran.dg/array_memset_2.f90 +++ b/gcc/testsuite/gfortran.dg/array_memset_2.f90 @@ -35,4 +35,3 @@ end program ! { dg-final { scan-tree-dump-times "= {}" 2 "original" } } ! { dg-final { cleanup-tree-dump "original" } } -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/array_temporaries_3.f90 b/gcc/testsuite/gfortran.dg/array_temporaries_3.f90 index 929a4c08e6bc..909c7ec5e7a4 100644 --- a/gcc/testsuite/gfortran.dg/array_temporaries_3.f90 +++ b/gcc/testsuite/gfortran.dg/array_temporaries_3.f90 @@ -27,5 +27,3 @@ end module bar call xmain if (c(1) .ne. "ab") call abort end -! { dg-final { cleanup-modules "bar" } } - diff --git a/gcc/testsuite/gfortran.dg/assignment_2.f90 b/gcc/testsuite/gfortran.dg/assignment_2.f90 index 18f303b368dc..a31082767ecb 100644 --- a/gcc/testsuite/gfortran.dg/assignment_2.f90 +++ b/gcc/testsuite/gfortran.dg/assignment_2.f90 @@ -46,5 +46,3 @@ contains REAL,INTENT(IN) :: b(:,:) END SUBROUTINE end module m3 - -! { dg-final { cleanup-modules "m1 m2 m3" } } diff --git a/gcc/testsuite/gfortran.dg/assignment_3.f90 b/gcc/testsuite/gfortran.dg/assignment_3.f90 index cdaaa8c5a4f0..d843c3200cb9 100644 --- a/gcc/testsuite/gfortran.dg/assignment_3.f90 +++ b/gcc/testsuite/gfortran.dg/assignment_3.f90 @@ -59,5 +59,3 @@ TYPE (distributed_vector) :: SCALP_DV ZTEMP = PVAZG * SCALP_DV END SUBROUTINE CAININAD_SCALE_DISTVEC END MODULE YOMCAIN - -! { dg-final { cleanup-modules "yomcain" } } diff --git a/gcc/testsuite/gfortran.dg/associate_6.f03 b/gcc/testsuite/gfortran.dg/associate_6.f03 index ba0e5c098098..356d388ef40d 100644 --- a/gcc/testsuite/gfortran.dg/associate_6.f03 +++ b/gcc/testsuite/gfortran.dg/associate_6.f03 @@ -34,6 +34,5 @@ PROGRAM main IF (arr(1) /= 1 .OR. arr(4) /= 4) CALL abort () END ASSOCIATE END PROGRAM main -! { dg-final { cleanup-modules "m" } } ! { dg-final { scan-tree-dump-times "func" 2 "original" } } ! { dg-final { cleanup-tree-dump "original" } } diff --git a/gcc/testsuite/gfortran.dg/associate_9.f03 b/gcc/testsuite/gfortran.dg/associate_9.f03 index 13a10fc0d9c6..3a262b6da092 100644 --- a/gcc/testsuite/gfortran.dg/associate_9.f03 +++ b/gcc/testsuite/gfortran.dg/associate_9.f03 @@ -48,4 +48,3 @@ PROGRAM main END PROGRAM main ! { dg-excess-errors "Syntex error in IF" } -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/associated_target_3.f90 b/gcc/testsuite/gfortran.dg/associated_target_3.f90 index e6a1d0f0adbd..423499a2f764 100644 --- a/gcc/testsuite/gfortran.dg/associated_target_3.f90 +++ b/gcc/testsuite/gfortran.dg/associated_target_3.f90 @@ -31,5 +31,3 @@ contains if (.not. associated (a, b)) call abort() end subroutine cmpPtr end - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/assumed_charlen_function_1.f90 b/gcc/testsuite/gfortran.dg/assumed_charlen_function_1.f90 index 13a79a6fe5db..a7f79391643d 100644 --- a/gcc/testsuite/gfortran.dg/assumed_charlen_function_1.f90 +++ b/gcc/testsuite/gfortran.dg/assumed_charlen_function_1.f90 @@ -77,4 +77,3 @@ end function not_OK END -! { dg-final { cleanup-modules "m1" } } diff --git a/gcc/testsuite/gfortran.dg/assumed_charlen_function_6.f90 b/gcc/testsuite/gfortran.dg/assumed_charlen_function_6.f90 index 49d1a2e55dd2..ed4f9dd05321 100644 --- a/gcc/testsuite/gfortran.dg/assumed_charlen_function_6.f90 +++ b/gcc/testsuite/gfortran.dg/assumed_charlen_function_6.f90 @@ -33,5 +33,3 @@ contains integer, intent(in) :: x end function assumed_len end program main - -! { dg-final { cleanup-modules "funcs mod2" } } diff --git a/gcc/testsuite/gfortran.dg/assumed_dummy_1.f90 b/gcc/testsuite/gfortran.dg/assumed_dummy_1.f90 index f8d7fea31a61..7935898d8797 100644 --- a/gcc/testsuite/gfortran.dg/assumed_dummy_1.f90 +++ b/gcc/testsuite/gfortran.dg/assumed_dummy_1.f90 @@ -42,5 +42,3 @@ contains x (2) = 21.0 END SUBROUTINE roo end program test - -! { dg-final { cleanup-modules "global" } } diff --git a/gcc/testsuite/gfortran.dg/assumed_shape_ranks_1.f90 b/gcc/testsuite/gfortran.dg/assumed_shape_ranks_1.f90 index e24414ad355a..a1c549bed8d7 100644 --- a/gcc/testsuite/gfortran.dg/assumed_shape_ranks_1.f90 +++ b/gcc/testsuite/gfortran.dg/assumed_shape_ranks_1.f90 @@ -22,5 +22,3 @@ CONTAINS write(6,*) I END SUBROUTINE TST END - -! { dg-final { cleanup-modules "addon" } } diff --git a/gcc/testsuite/gfortran.dg/assumed_shape_ranks_2.f90 b/gcc/testsuite/gfortran.dg/assumed_shape_ranks_2.f90 index da59213d91ff..641d3d929f4f 100644 --- a/gcc/testsuite/gfortran.dg/assumed_shape_ranks_2.f90 +++ b/gcc/testsuite/gfortran.dg/assumed_shape_ranks_2.f90 @@ -43,5 +43,3 @@ end module mod1 call foo (bar, i) if (i .ne. 2) call abort () end - -! { dg-final { cleanup-modules "mod1" } } diff --git a/gcc/testsuite/gfortran.dg/assumed_size_dt_dummy.f90 b/gcc/testsuite/gfortran.dg/assumed_size_dt_dummy.f90 index 7e84e9e60adc..06f0f7592f1f 100644 --- a/gcc/testsuite/gfortran.dg/assumed_size_dt_dummy.f90 +++ b/gcc/testsuite/gfortran.dg/assumed_size_dt_dummy.f90 @@ -14,5 +14,3 @@ CONTAINS END MODULE TEST end - -! { dg-final { cleanup-modules "test" } } diff --git a/gcc/testsuite/gfortran.dg/assumed_type_1.f90 b/gcc/testsuite/gfortran.dg/assumed_type_1.f90 index 7ac98f82738d..637b39387f04 100644 --- a/gcc/testsuite/gfortran.dg/assumed_type_1.f90 +++ b/gcc/testsuite/gfortran.dg/assumed_type_1.f90 @@ -52,5 +52,3 @@ contains call MPI_Send2(x, 1, 1,1,1,j,i) end end - -! { dg-final { cleanup-modules "mpi_interface" } } diff --git a/gcc/testsuite/gfortran.dg/assumed_type_2.f90 b/gcc/testsuite/gfortran.dg/assumed_type_2.f90 index b88717c0f05b..ab1049d216eb 100644 --- a/gcc/testsuite/gfortran.dg/assumed_type_2.f90 +++ b/gcc/testsuite/gfortran.dg/assumed_type_2.f90 @@ -139,8 +139,6 @@ deallocate (array_class_t1_ptr, array_t3_ptr) end -! { dg-final { cleanup-modules "mod" } } - ! { dg-final { scan-tree-dump-times "sub_scalar .0B," 2 "original" } } ! { dg-final { scan-tree-dump-times "sub_scalar .scalar_real_alloc," 2 "original" } } ! { dg-final { scan-tree-dump-times "sub_scalar .scalar_char_ptr," 2 "original" } } diff --git a/gcc/testsuite/gfortran.dg/auto_char_dummy_array_1.f90 b/gcc/testsuite/gfortran.dg/auto_char_dummy_array_1.f90 index 6ed6f45769f0..6a660c203883 100644 --- a/gcc/testsuite/gfortran.dg/auto_char_dummy_array_1.f90 +++ b/gcc/testsuite/gfortran.dg/auto_char_dummy_array_1.f90 @@ -53,5 +53,3 @@ contains end subroutine a end program oh_no_not_pr15908_again - -! { dg-final { cleanup-modules "global" } } diff --git a/gcc/testsuite/gfortran.dg/auto_char_len_3.f90 b/gcc/testsuite/gfortran.dg/auto_char_len_3.f90 index da8cf5e4e784..b94151148af4 100644 --- a/gcc/testsuite/gfortran.dg/auto_char_len_3.f90 +++ b/gcc/testsuite/gfortran.dg/auto_char_len_3.f90 @@ -23,5 +23,3 @@ program TestStringTools if (txt .ne. "AaBbCcDdEeFfGgHhIiJjKkLlMmNnOoPpQqRrSsTtUuVvWwXxYyZz") & call abort () end program TestStringTools - -! { dg-final { cleanup-modules "chtest" } } diff --git a/gcc/testsuite/gfortran.dg/auto_dealloc_1.f90 b/gcc/testsuite/gfortran.dg/auto_dealloc_1.f90 index 95a71609d1dc..7e5fbd1486e6 100644 --- a/gcc/testsuite/gfortran.dg/auto_dealloc_1.f90 +++ b/gcc/testsuite/gfortran.dg/auto_dealloc_1.f90 @@ -54,6 +54,4 @@ end module ! { dg-final { scan-tree-dump-times "__builtin_free" 4 "original" } } - -! { dg-final { cleanup-modules "automatic_deallocation" } } ! { dg-final { cleanup-tree-dump "original" } } diff --git a/gcc/testsuite/gfortran.dg/automatic_default_init_1.f90 b/gcc/testsuite/gfortran.dg/automatic_default_init_1.f90 index 525632b36d05..178706a34224 100644 --- a/gcc/testsuite/gfortran.dg/automatic_default_init_1.f90 +++ b/gcc/testsuite/gfortran.dg/automatic_default_init_1.f90 @@ -18,4 +18,3 @@ END MODULE M1 USE M1 CALL S1(2) END -! { dg-final { cleanup-modules "m1" } } diff --git a/gcc/testsuite/gfortran.dg/automatic_module_variable.f90 b/gcc/testsuite/gfortran.dg/automatic_module_variable.f90 index c88b355b24c3..201dcf4e1d3c 100644 --- a/gcc/testsuite/gfortran.dg/automatic_module_variable.f90 +++ b/gcc/testsuite/gfortran.dg/automatic_module_variable.f90 @@ -14,5 +14,3 @@ contains init = x end function init end module sd - -! { dg-final { cleanup-modules "sd" } } diff --git a/gcc/testsuite/gfortran.dg/bad_automatic_objects_1.f90 b/gcc/testsuite/gfortran.dg/bad_automatic_objects_1.f90 index c4c1f2cb0ccd..273441861947 100644 --- a/gcc/testsuite/gfortran.dg/bad_automatic_objects_1.f90 +++ b/gcc/testsuite/gfortran.dg/bad_automatic_objects_1.f90 @@ -18,5 +18,3 @@ program foobar integer, dimension (i) :: k ! { dg-error "must have constant shape" } character (len = i) :: c2 ! { dg-error "must have constant character length" } end program foobar - -! { dg-final { cleanup-modules "foo bar" } } diff --git a/gcc/testsuite/gfortran.dg/bind_c_coms.f90 b/gcc/testsuite/gfortran.dg/bind_c_coms.f90 index e88d56d182ca..85ead9fb636a 100644 --- a/gcc/testsuite/gfortran.dg/bind_c_coms.f90 +++ b/gcc/testsuite/gfortran.dg/bind_c_coms.f90 @@ -47,5 +47,3 @@ module bind_c_coms_2 integer(c_int) :: m, n bind(c, name="") /com3/ end module bind_c_coms_2 - -! { dg-final { cleanup-modules "bind_c_coms bind_c_coms_2" } } diff --git a/gcc/testsuite/gfortran.dg/bind_c_dts.f90 b/gcc/testsuite/gfortran.dg/bind_c_dts.f90 index f0a31e5408e3..f78630ba5604 100644 --- a/gcc/testsuite/gfortran.dg/bind_c_dts.f90 +++ b/gcc/testsuite/gfortran.dg/bind_c_dts.f90 @@ -39,5 +39,3 @@ contains myDerived%s = myDerived%s + 1.0; end subroutine types_test end module bind_c_dts - -! { dg-final { cleanup-modules "bind_c_dts" } } diff --git a/gcc/testsuite/gfortran.dg/bind_c_dts_2.f03 b/gcc/testsuite/gfortran.dg/bind_c_dts_2.f03 index 4b423e53de4c..4e5e61b4ee8a 100644 --- a/gcc/testsuite/gfortran.dg/bind_c_dts_2.f03 +++ b/gcc/testsuite/gfortran.dg/bind_c_dts_2.f03 @@ -59,5 +59,3 @@ contains end if end subroutine sub0 end module bind_c_dts_2 - -! { dg-final { cleanup-modules "bind_c_dts_2" } } diff --git a/gcc/testsuite/gfortran.dg/bind_c_dts_3.f03 b/gcc/testsuite/gfortran.dg/bind_c_dts_3.f03 index fa54fb761be3..e28769ddf846 100644 --- a/gcc/testsuite/gfortran.dg/bind_c_dts_3.f03 +++ b/gcc/testsuite/gfortran.dg/bind_c_dts_3.f03 @@ -35,5 +35,3 @@ contains end if end subroutine sub0 end module bind_c_dts_3 - -! { dg-final { cleanup-modules "bind_c_dts_3" } } diff --git a/gcc/testsuite/gfortran.dg/bind_c_dts_4.f03 b/gcc/testsuite/gfortran.dg/bind_c_dts_4.f03 index c6fc40244439..1e42d5b9bece 100644 --- a/gcc/testsuite/gfortran.dg/bind_c_dts_4.f03 +++ b/gcc/testsuite/gfortran.dg/bind_c_dts_4.f03 @@ -7,5 +7,3 @@ use iso_c_binding, only: c_int end type type(foo), bind(c) :: cp end module test - -! { dg-final { cleanup-modules "test" } } diff --git a/gcc/testsuite/gfortran.dg/bind_c_dts_5.f90 b/gcc/testsuite/gfortran.dg/bind_c_dts_5.f90 index 497c0501b111..5fe5e2b36ccc 100644 --- a/gcc/testsuite/gfortran.dg/bind_c_dts_5.f90 +++ b/gcc/testsuite/gfortran.dg/bind_c_dts_5.f90 @@ -50,5 +50,3 @@ PROGRAM main write (*,*) liter_cb(link_info) END PROGRAM main - -! { dg-final { cleanup-modules "liter_cb_mod" } } diff --git a/gcc/testsuite/gfortran.dg/bind_c_implicit_vars.f03 b/gcc/testsuite/gfortran.dg/bind_c_implicit_vars.f03 index bac7d4d58159..5df783fcf2dc 100644 --- a/gcc/testsuite/gfortran.dg/bind_c_implicit_vars.f03 +++ b/gcc/testsuite/gfortran.dg/bind_c_implicit_vars.f03 @@ -9,5 +9,3 @@ contains i = 0 end subroutine sub0 end module bind_c_implicit_vars - -! { dg-final { cleanup-modules "bind_c_implicit_vars" } } diff --git a/gcc/testsuite/gfortran.dg/bind_c_module.f90 b/gcc/testsuite/gfortran.dg/bind_c_module.f90 index a17f5d0b34b1..6cb7387a46a6 100644 --- a/gcc/testsuite/gfortran.dg/bind_c_module.f90 +++ b/gcc/testsuite/gfortran.dg/bind_c_module.f90 @@ -19,4 +19,3 @@ module d implicit none bind(c) :: a ! { dg-error "applied to" } end module d -! { dg-final { cleanup-modules "a" } } diff --git a/gcc/testsuite/gfortran.dg/bind_c_procs.f03 b/gcc/testsuite/gfortran.dg/bind_c_procs.f03 index 718042bafcbe..eaf067289d8e 100644 --- a/gcc/testsuite/gfortran.dg/bind_c_procs.f03 +++ b/gcc/testsuite/gfortran.dg/bind_c_procs.f03 @@ -35,5 +35,3 @@ contains end function my_f03_func end module bind_c_procs - -! { dg-final { cleanup-modules "bind_c_procs" } } diff --git a/gcc/testsuite/gfortran.dg/bind_c_usage_10.f03 b/gcc/testsuite/gfortran.dg/bind_c_usage_10.f03 index 4f2268aee6db..c6f2b79c1faa 100644 --- a/gcc/testsuite/gfortran.dg/bind_c_usage_10.f03 +++ b/gcc/testsuite/gfortran.dg/bind_c_usage_10.f03 @@ -71,5 +71,3 @@ contains func4ent = -88.0 end function func4 end module mod - -! { dg-final { cleanup-modules "mod" } } diff --git a/gcc/testsuite/gfortran.dg/bind_c_usage_15.f90 b/gcc/testsuite/gfortran.dg/bind_c_usage_15.f90 index 55caba45f5f4..c5201a634db6 100644 --- a/gcc/testsuite/gfortran.dg/bind_c_usage_15.f90 +++ b/gcc/testsuite/gfortran.dg/bind_c_usage_15.f90 @@ -27,5 +27,3 @@ program main call gen(x) if(x /= 17) call abort() end program main - -! { dg-final { cleanup-modules "mod" } } diff --git a/gcc/testsuite/gfortran.dg/bind_c_usage_16.f03 b/gcc/testsuite/gfortran.dg/bind_c_usage_16.f03 index 68b043cba4b3..990918fcc59f 100644 --- a/gcc/testsuite/gfortran.dg/bind_c_usage_16.f03 +++ b/gcc/testsuite/gfortran.dg/bind_c_usage_16.f03 @@ -55,5 +55,3 @@ subroutine test() bind(c) if(iachar(d(i)(2:2)) /=32 .or. iachar(d(i)(3:3)) /= 32) call abort() end do end subroutine - -! { dg-final { cleanup-modules "mod" } } diff --git a/gcc/testsuite/gfortran.dg/bind_c_usage_17.f90 b/gcc/testsuite/gfortran.dg/bind_c_usage_17.f90 index ba342755c38f..ad7ffd08f3d4 100644 --- a/gcc/testsuite/gfortran.dg/bind_c_usage_17.f90 +++ b/gcc/testsuite/gfortran.dg/bind_c_usage_17.f90 @@ -34,5 +34,3 @@ PROGRAM test WRITE(str4,'(i0)') ICHAR(cdir()) if(str4 /= '47' .or. ichar(str4(3:3)) /= 32) call abort() END PROGRAM - -! { dg-final { cleanup-modules "mod" } } diff --git a/gcc/testsuite/gfortran.dg/bind_c_usage_21.f90 b/gcc/testsuite/gfortran.dg/bind_c_usage_21.f90 index 10a86dbbbc41..3ed8dc90a461 100644 --- a/gcc/testsuite/gfortran.dg/bind_c_usage_21.f90 +++ b/gcc/testsuite/gfortran.dg/bind_c_usage_21.f90 @@ -21,5 +21,3 @@ contains liter_cb = 0 END FUNCTION liter_cb end module m - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/bind_c_usage_24.f90 b/gcc/testsuite/gfortran.dg/bind_c_usage_24.f90 index a6ebd5833c1c..a46772be2496 100644 --- a/gcc/testsuite/gfortran.dg/bind_c_usage_24.f90 +++ b/gcc/testsuite/gfortran.dg/bind_c_usage_24.f90 @@ -39,5 +39,3 @@ program test call c_proc (.true._c_bool, val) if (val /= 7) call abort () end program test - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/bind_c_usage_25.f90 b/gcc/testsuite/gfortran.dg/bind_c_usage_25.f90 index 087a9e05ac97..ae3cf07fcb8e 100644 --- a/gcc/testsuite/gfortran.dg/bind_c_usage_25.f90 +++ b/gcc/testsuite/gfortran.dg/bind_c_usage_25.f90 @@ -56,8 +56,3 @@ module c_kind_tests_2 real(myI), bind(c) :: myCFloat2 ! { dg-warning "is for type INTEGER" } real(4), bind(c) :: myFloat end module c_kind_tests_2 - -! { dg-final { cleanup-modules "c_kind_tests_2" } } -! { dg-final { cleanup-modules "bind_c_implicit_vars" } } -! { dg-final { cleanup-modules "test" } } -! { dg-final { cleanup-modules "iso_c_utilities" } } diff --git a/gcc/testsuite/gfortran.dg/bind_c_usage_3.f03 b/gcc/testsuite/gfortran.dg/bind_c_usage_3.f03 index 8f070335aa80..47f9d9a92183 100644 --- a/gcc/testsuite/gfortran.dg/bind_c_usage_3.f03 +++ b/gcc/testsuite/gfortran.dg/bind_c_usage_3.f03 @@ -17,4 +17,3 @@ module test type(foo), bind(c) :: cp ! { dg-error "is not C interoperable" } real(c_double), pointer,bind(c) :: p ! { dg-error "cannot have both the POINTER and BIND.C." } end module test -! { dg-final { cleanup-modules "test" } } diff --git a/gcc/testsuite/gfortran.dg/bind_c_usage_7.f03 b/gcc/testsuite/gfortran.dg/bind_c_usage_7.f03 index 845aab953222..25adb2c7f15c 100644 --- a/gcc/testsuite/gfortran.dg/bind_c_usage_7.f03 +++ b/gcc/testsuite/gfortran.dg/bind_c_usage_7.f03 @@ -12,5 +12,3 @@ contains my_string_func = 'my_string' // C_NULL_CHAR end function my_string_func end module x - -! { dg-final { cleanup-modules "x" } } diff --git a/gcc/testsuite/gfortran.dg/bind_c_usage_8.f03 b/gcc/testsuite/gfortran.dg/bind_c_usage_8.f03 index e31af86bffd0..15843b5c9d67 100644 --- a/gcc/testsuite/gfortran.dg/bind_c_usage_8.f03 +++ b/gcc/testsuite/gfortran.dg/bind_c_usage_8.f03 @@ -22,5 +22,3 @@ CONTAINS CALL C_F_POINTER(FPTR=FPTR, CPTR=CPTR, SHAPE=[strlen(CPTR)]) END FUNCTION END MODULE ISO_C_UTILITIES -! { dg-final { cleanup-modules "iso_c_utilities" } } - diff --git a/gcc/testsuite/gfortran.dg/bind_c_vars.f90 b/gcc/testsuite/gfortran.dg/bind_c_vars.f90 index e57edf09d38c..4f4a0cfd795b 100644 --- a/gcc/testsuite/gfortran.dg/bind_c_vars.f90 +++ b/gcc/testsuite/gfortran.dg/bind_c_vars.f90 @@ -36,5 +36,3 @@ contains end subroutine changeF90Globals end module bind_c_vars - -! { dg-final { cleanup-modules "bind_c_vars" } } diff --git a/gcc/testsuite/gfortran.dg/binding_label_tests.f03 b/gcc/testsuite/gfortran.dg/binding_label_tests.f03 index 34986501e296..a13e9673aa09 100644 --- a/gcc/testsuite/gfortran.dg/binding_label_tests.f03 +++ b/gcc/testsuite/gfortran.dg/binding_label_tests.f03 @@ -73,5 +73,3 @@ module binding_label_tests subroutine sub4() BIND(c, name = " ") end subroutine sub4 end module binding_label_tests - -! { dg-final { cleanup-modules "binding_label_tests" } } diff --git a/gcc/testsuite/gfortran.dg/binding_label_tests_10_main.f03 b/gcc/testsuite/gfortran.dg/binding_label_tests_10_main.f03 index 48e8e5da9b1e..8424922d4304 100644 --- a/gcc/testsuite/gfortran.dg/binding_label_tests_10_main.f03 +++ b/gcc/testsuite/gfortran.dg/binding_label_tests_10_main.f03 @@ -11,4 +11,3 @@ program main use binding_label_tests_10 ! { dg-error "collides" } use binding_label_tests_10_main end program main -! { dg-final { cleanup-modules "binding_label_tests_10" } } diff --git a/gcc/testsuite/gfortran.dg/binding_label_tests_12.f03 b/gcc/testsuite/gfortran.dg/binding_label_tests_12.f03 index 0a0006681154..ce9cd9f93a74 100644 --- a/gcc/testsuite/gfortran.dg/binding_label_tests_12.f03 +++ b/gcc/testsuite/gfortran.dg/binding_label_tests_12.f03 @@ -20,5 +20,3 @@ end module two use one, only: foo_one => foo use two, only: foo_two => foo end - -! { dg-final { cleanup-modules "one two" } } diff --git a/gcc/testsuite/gfortran.dg/binding_label_tests_16.f03 b/gcc/testsuite/gfortran.dg/binding_label_tests_16.f03 index 6b8f1f89bac8..7029b2ea1915 100644 --- a/gcc/testsuite/gfortran.dg/binding_label_tests_16.f03 +++ b/gcc/testsuite/gfortran.dg/binding_label_tests_16.f03 @@ -19,4 +19,3 @@ implicit none print *, a, b if (a /= 5 .or. b /= -5) call abort() end program prog -! { dg-final { cleanup-modules "m n" } } diff --git a/gcc/testsuite/gfortran.dg/binding_label_tests_2.f03 b/gcc/testsuite/gfortran.dg/binding_label_tests_2.f03 index bf9da112ab4f..46bbbbd04ceb 100644 --- a/gcc/testsuite/gfortran.dg/binding_label_tests_2.f03 +++ b/gcc/testsuite/gfortran.dg/binding_label_tests_2.f03 @@ -31,5 +31,3 @@ contains subroutine sub8() bind(c, name) ! { dg-error "Syntax error" } end subroutine sub8 ! { dg-error "Expecting END MODULE" } end module binding_label_tests_2 - -! { dg-final { cleanup-modules "binding_label_tests_2" } } diff --git a/gcc/testsuite/gfortran.dg/binding_label_tests_7.f03 b/gcc/testsuite/gfortran.dg/binding_label_tests_7.f03 index 136fb5e507c0..1234bb535387 100644 --- a/gcc/testsuite/gfortran.dg/binding_label_tests_7.f03 +++ b/gcc/testsuite/gfortran.dg/binding_label_tests_7.f03 @@ -13,5 +13,3 @@ end interface call my_c_print() end program main - -! { dg-final { cleanup-modules "a" } } diff --git a/gcc/testsuite/gfortran.dg/binding_label_tests_9.f03 b/gcc/testsuite/gfortran.dg/binding_label_tests_9.f03 index cdf1ef880dfd..bb61cbf12c77 100644 --- a/gcc/testsuite/gfortran.dg/binding_label_tests_9.f03 +++ b/gcc/testsuite/gfortran.dg/binding_label_tests_9.f03 @@ -19,5 +19,3 @@ contains subroutine my_public_sub() bind(c, name="my_sub") end subroutine my_public_sub end module x - -! { dg-final { cleanup-modules "x" } } diff --git a/gcc/testsuite/gfortran.dg/block_11.f90 b/gcc/testsuite/gfortran.dg/block_11.f90 index 83c6519d970f..2c2ce9083f61 100644 --- a/gcc/testsuite/gfortran.dg/block_11.f90 +++ b/gcc/testsuite/gfortran.dg/block_11.f90 @@ -64,5 +64,3 @@ contains end module m3 end - -! { dg-final { cleanup-modules "testmod testmod2 m3" } } diff --git a/gcc/testsuite/gfortran.dg/bound_simplification_2.f90 b/gcc/testsuite/gfortran.dg/bound_simplification_2.f90 index 05477776f080..a3f1e4321f1d 100644 --- a/gcc/testsuite/gfortran.dg/bound_simplification_2.f90 +++ b/gcc/testsuite/gfortran.dg/bound_simplification_2.f90 @@ -6,4 +6,3 @@ module foo INTEGER, PARAMETER, DIMENSION(2) :: IP_ARRAY1_32_S = & & (/ LBOUND(IP_ARRAY2_4_S(5:10,2:3))/) END module foo -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/bounds_check_9.f90 b/gcc/testsuite/gfortran.dg/bounds_check_9.f90 index 3b487efa146c..c0abd2896ece 100644 --- a/gcc/testsuite/gfortran.dg/bounds_check_9.f90 +++ b/gcc/testsuite/gfortran.dg/bounds_check_9.f90 @@ -34,4 +34,3 @@ program main call sub() call sub((/4,5/)) end program main -! { dg-final { cleanup-modules "sub_mod" } } diff --git a/gcc/testsuite/gfortran.dg/bounds_check_fail_2.f90 b/gcc/testsuite/gfortran.dg/bounds_check_fail_2.f90 index d79272b3876e..bb2c247bf311 100644 --- a/gcc/testsuite/gfortran.dg/bounds_check_fail_2.f90 +++ b/gcc/testsuite/gfortran.dg/bounds_check_fail_2.f90 @@ -37,4 +37,3 @@ program main call sub((/4/)) end program main ! { dg-output "Fortran runtime error: Array bound mismatch" } -! { dg-final { cleanup-modules "sub_mod" } } diff --git a/gcc/testsuite/gfortran.dg/bounds_check_strlen_2.f90 b/gcc/testsuite/gfortran.dg/bounds_check_strlen_2.f90 index 7ecce2a71d49..241db66239cd 100644 --- a/gcc/testsuite/gfortran.dg/bounds_check_strlen_2.f90 +++ b/gcc/testsuite/gfortran.dg/bounds_check_strlen_2.f90 @@ -30,4 +30,3 @@ PROGRAM main END PROGRAM main ! { dg-output "shorter than the declared one for dummy argument 'str' \\(3/5\\)" } -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/bounds_check_strlen_3.f90 b/gcc/testsuite/gfortran.dg/bounds_check_strlen_3.f90 index 69be0884c3b7..a6be86a8c4a2 100644 --- a/gcc/testsuite/gfortran.dg/bounds_check_strlen_3.f90 +++ b/gcc/testsuite/gfortran.dg/bounds_check_strlen_3.f90 @@ -30,4 +30,3 @@ PROGRAM main END PROGRAM main ! { dg-output "does not match the declared one for dummy argument 'str' \\(7/5\\)" } -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/bounds_check_strlen_4.f90 b/gcc/testsuite/gfortran.dg/bounds_check_strlen_4.f90 index db8ce3c3b118..284e2eae38ff 100644 --- a/gcc/testsuite/gfortran.dg/bounds_check_strlen_4.f90 +++ b/gcc/testsuite/gfortran.dg/bounds_check_strlen_4.f90 @@ -30,4 +30,3 @@ PROGRAM main END PROGRAM main ! { dg-output "does not match the declared one for dummy argument 'str' \\(7/5\\)" } -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/bounds_check_strlen_5.f90 b/gcc/testsuite/gfortran.dg/bounds_check_strlen_5.f90 index 36fda721f303..48202488246d 100644 --- a/gcc/testsuite/gfortran.dg/bounds_check_strlen_5.f90 +++ b/gcc/testsuite/gfortran.dg/bounds_check_strlen_5.f90 @@ -30,4 +30,3 @@ PROGRAM main END PROGRAM main ! { dg-output "does not match the declared one for dummy argument 'str' \\(7/5\\)" } -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/bounds_check_strlen_6.f90 b/gcc/testsuite/gfortran.dg/bounds_check_strlen_6.f90 index 550cca8431f4..c46bfe2db231 100644 --- a/gcc/testsuite/gfortran.dg/bounds_check_strlen_6.f90 +++ b/gcc/testsuite/gfortran.dg/bounds_check_strlen_6.f90 @@ -24,5 +24,3 @@ PROGRAM main CALL test ('abcde') ! String length matches. CALL test ('abcdef') ! String too long, is ok. END PROGRAM main - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/bounds_check_strlen_7.f90 b/gcc/testsuite/gfortran.dg/bounds_check_strlen_7.f90 index 9f08ba1ca8f4..99a0d8697ff6 100644 --- a/gcc/testsuite/gfortran.dg/bounds_check_strlen_7.f90 +++ b/gcc/testsuite/gfortran.dg/bounds_check_strlen_7.f90 @@ -22,4 +22,3 @@ PROGRAM main END PROGRAM main ! { dg-output "shorter than the declared one for dummy argument 'opt' \\(0/5\\)" } -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/bounds_check_strlen_8.f90 b/gcc/testsuite/gfortran.dg/bounds_check_strlen_8.f90 index c54f14144f83..7319988968f0 100644 --- a/gcc/testsuite/gfortran.dg/bounds_check_strlen_8.f90 +++ b/gcc/testsuite/gfortran.dg/bounds_check_strlen_8.f90 @@ -36,5 +36,3 @@ END MODULE M3 USE M3 CALL S1 END - -! { dg-final { cleanup-modules "m1 m2 m3" } } diff --git a/gcc/testsuite/gfortran.dg/c_assoc.f90 b/gcc/testsuite/gfortran.dg/c_assoc.f90 index 7b34663a3405..9b2af24f9848 100644 --- a/gcc/testsuite/gfortran.dg/c_assoc.f90 +++ b/gcc/testsuite/gfortran.dg/c_assoc.f90 @@ -66,5 +66,3 @@ contains end subroutine verify_assoc end module c_assoc - -! { dg-final { cleanup-modules "c_assoc" } } diff --git a/gcc/testsuite/gfortran.dg/c_by_val_5.f90 b/gcc/testsuite/gfortran.dg/c_by_val_5.f90 index 90ef299aa920..069d81711756 100644 --- a/gcc/testsuite/gfortran.dg/c_by_val_5.f90 +++ b/gcc/testsuite/gfortran.dg/c_by_val_5.f90 @@ -65,5 +65,3 @@ program main call Grid2BMP(10) ! call test() end program main - -! { dg-final { cleanup-modules "x" } } diff --git a/gcc/testsuite/gfortran.dg/c_char_tests.f03 b/gcc/testsuite/gfortran.dg/c_char_tests.f03 index 72b136e01d08..cbdfd9f2a9ac 100644 --- a/gcc/testsuite/gfortran.dg/c_char_tests.f03 +++ b/gcc/testsuite/gfortran.dg/c_char_tests.f03 @@ -25,5 +25,3 @@ contains if(my_char_ref /= c_char_'y') call abort() end subroutine sub1 end module c_char_tests - -! { dg-final { cleanup-modules "c_char_tests" } } diff --git a/gcc/testsuite/gfortran.dg/c_f_pointer_complex.f03 b/gcc/testsuite/gfortran.dg/c_f_pointer_complex.f03 index fd9703139e5c..b68eadbf9ab6 100644 --- a/gcc/testsuite/gfortran.dg/c_f_pointer_complex.f03 +++ b/gcc/testsuite/gfortran.dg/c_f_pointer_complex.f03 @@ -57,5 +57,3 @@ contains end do end subroutine test_complex_arrays end module c_f_pointer_complex -! { dg-final { cleanup-modules "c_f_pointer_complex" } } - diff --git a/gcc/testsuite/gfortran.dg/c_f_pointer_logical.f03 b/gcc/testsuite/gfortran.dg/c_f_pointer_logical.f03 index 977c4cb070d0..5558697c1f55 100644 --- a/gcc/testsuite/gfortran.dg/c_f_pointer_logical.f03 +++ b/gcc/testsuite/gfortran.dg/c_f_pointer_logical.f03 @@ -31,4 +31,3 @@ contains end do end subroutine test_array end module c_f_pointer_logical -! { dg-final { cleanup-modules "c_f_pointer_logical" } } diff --git a/gcc/testsuite/gfortran.dg/c_f_pointer_shape_tests_2.f03 b/gcc/testsuite/gfortran.dg/c_f_pointer_shape_tests_2.f03 index 662908931b99..426279b5cfb1 100644 --- a/gcc/testsuite/gfortran.dg/c_f_pointer_shape_tests_2.f03 +++ b/gcc/testsuite/gfortran.dg/c_f_pointer_shape_tests_2.f03 @@ -110,5 +110,3 @@ contains end do end subroutine test_mixed end module c_f_pointer_shape_tests_2 -! { dg-final { cleanup-modules "c_f_pointer_shape_tests_2" } } - diff --git a/gcc/testsuite/gfortran.dg/c_f_pointer_shape_tests_4.f03 b/gcc/testsuite/gfortran.dg/c_f_pointer_shape_tests_4.f03 index 89b8666d7ae4..b3caff0a5a9b 100644 --- a/gcc/testsuite/gfortran.dg/c_f_pointer_shape_tests_4.f03 +++ b/gcc/testsuite/gfortran.dg/c_f_pointer_shape_tests_4.f03 @@ -111,5 +111,3 @@ contains end do end subroutine test_mixed end module c_f_pointer_shape_tests_4 -! { dg-final { cleanup-modules "c_f_pointer_shape_tests_4" } } - diff --git a/gcc/testsuite/gfortran.dg/c_f_pointer_tests.f90 b/gcc/testsuite/gfortran.dg/c_f_pointer_tests.f90 index d35f9d1c151c..1e4dbc0201fd 100644 --- a/gcc/testsuite/gfortran.dg/c_f_pointer_tests.f90 +++ b/gcc/testsuite/gfortran.dg/c_f_pointer_tests.f90 @@ -66,5 +66,3 @@ module c_f_pointer_tests endif end subroutine testDerivedPtrs end module c_f_pointer_tests - -! { dg-final { cleanup-modules "c_f_pointer_tests" } } diff --git a/gcc/testsuite/gfortran.dg/c_funloc_tests.f03 b/gcc/testsuite/gfortran.dg/c_funloc_tests.f03 index 8ba07b9fbba1..823c5e39d2a9 100644 --- a/gcc/testsuite/gfortran.dg/c_funloc_tests.f03 +++ b/gcc/testsuite/gfortran.dg/c_funloc_tests.f03 @@ -17,5 +17,3 @@ program driver call sub0() end program driver - -! { dg-final { cleanup-modules "c_funloc_tests" } } diff --git a/gcc/testsuite/gfortran.dg/c_funloc_tests_3.f03 b/gcc/testsuite/gfortran.dg/c_funloc_tests_3.f03 index 2d23efb243a9..b08d35187f4f 100644 --- a/gcc/testsuite/gfortran.dg/c_funloc_tests_3.f03 +++ b/gcc/testsuite/gfortran.dg/c_funloc_tests_3.f03 @@ -33,4 +33,3 @@ program main p = c_funloc(ffunc) call callFunc(p, 21,-17*21) end program main -! { dg-final { cleanup-modules "c_funloc_tests_3" } } diff --git a/gcc/testsuite/gfortran.dg/c_funloc_tests_4.f03 b/gcc/testsuite/gfortran.dg/c_funloc_tests_4.f03 index 0733c5e20b1f..16a50668706e 100644 --- a/gcc/testsuite/gfortran.dg/c_funloc_tests_4.f03 +++ b/gcc/testsuite/gfortran.dg/c_funloc_tests_4.f03 @@ -36,5 +36,3 @@ contains func0 = desired_retval end function func0 end module c_funloc_tests_4 -! { dg-final { cleanup-modules "c_funloc_tests_4" } } - diff --git a/gcc/testsuite/gfortran.dg/c_kind_params.f90 b/gcc/testsuite/gfortran.dg/c_kind_params.f90 index 4176157887a1..c595a3bbcf00 100644 --- a/gcc/testsuite/gfortran.dg/c_kind_params.f90 +++ b/gcc/testsuite/gfortran.dg/c_kind_params.f90 @@ -74,4 +74,3 @@ contains end subroutine param_test end module c_kind_params -! { dg-final { cleanup-modules "c_kind_params" } } diff --git a/gcc/testsuite/gfortran.dg/c_kind_tests_2.f03 b/gcc/testsuite/gfortran.dg/c_kind_tests_2.f03 index 5bc99f55387c..592953c0c005 100644 --- a/gcc/testsuite/gfortran.dg/c_kind_tests_2.f03 +++ b/gcc/testsuite/gfortran.dg/c_kind_tests_2.f03 @@ -13,4 +13,3 @@ module c_kind_tests_2 real(myI), bind(c) :: myCFloat2 ! { dg-warning "is for type INTEGER" } real(4), bind(c) :: myFloat ! { dg-warning "may not be a C interoperable" } end module c_kind_tests_2 -! { dg-final { cleanup-modules "c_kind_tests_2" } } diff --git a/gcc/testsuite/gfortran.dg/c_loc_test.f90 b/gcc/testsuite/gfortran.dg/c_loc_test.f90 index 673e6f7282ee..9b120dc9cd2f 100644 --- a/gcc/testsuite/gfortran.dg/c_loc_test.f90 +++ b/gcc/testsuite/gfortran.dg/c_loc_test.f90 @@ -21,4 +21,3 @@ contains call test_address(my_c_ptr, 100) end subroutine test0 end module c_loc_test -! { dg-final { cleanup-modules "c_loc_test" } } diff --git a/gcc/testsuite/gfortran.dg/c_loc_tests_12.f03 b/gcc/testsuite/gfortran.dg/c_loc_tests_12.f03 index 252c1c52748d..cfc7be5eb443 100644 --- a/gcc/testsuite/gfortran.dg/c_loc_tests_12.f03 +++ b/gcc/testsuite/gfortran.dg/c_loc_tests_12.f03 @@ -29,4 +29,3 @@ program test2 call sub1(c_loc(argv)) end program test2 ! -! { dg-final { cleanup-modules "test1" } } diff --git a/gcc/testsuite/gfortran.dg/c_loc_tests_2.f03 b/gcc/testsuite/gfortran.dg/c_loc_tests_2.f03 index 4bdf395d14b5..b8e2436b679f 100644 --- a/gcc/testsuite/gfortran.dg/c_loc_tests_2.f03 +++ b/gcc/testsuite/gfortran.dg/c_loc_tests_2.f03 @@ -85,4 +85,3 @@ program driver call test1() call test2() end program driver -! { dg-final { cleanup-modules "c_loc_tests_2" } } diff --git a/gcc/testsuite/gfortran.dg/c_loc_tests_5.f03 b/gcc/testsuite/gfortran.dg/c_loc_tests_5.f03 index a389437ce109..48597cb6bd8d 100644 --- a/gcc/testsuite/gfortran.dg/c_loc_tests_5.f03 +++ b/gcc/testsuite/gfortran.dg/c_loc_tests_5.f03 @@ -16,4 +16,3 @@ contains end subroutine sub0 end module c_loc_tests_5 -! { dg-final { cleanup-modules "c_loc_tests_5" } } diff --git a/gcc/testsuite/gfortran.dg/c_loc_tests_6.f03 b/gcc/testsuite/gfortran.dg/c_loc_tests_6.f03 index c82a2adbf788..3d830e7a91f4 100644 --- a/gcc/testsuite/gfortran.dg/c_loc_tests_6.f03 +++ b/gcc/testsuite/gfortran.dg/c_loc_tests_6.f03 @@ -10,4 +10,3 @@ SUBROUTINE glutInit_f03() argv(1)=C_LOC(empty_string) END SUBROUTINE end module x -! { dg-final { cleanup-modules "x" } } diff --git a/gcc/testsuite/gfortran.dg/c_loc_tests_7.f03 b/gcc/testsuite/gfortran.dg/c_loc_tests_7.f03 index 78f5276bdefc..cc0ebc365fa5 100644 --- a/gcc/testsuite/gfortran.dg/c_loc_tests_7.f03 +++ b/gcc/testsuite/gfortran.dg/c_loc_tests_7.f03 @@ -8,4 +8,3 @@ SUBROUTINE glutInit_f03() argv(1)=C_LOC(empty_string) END SUBROUTINE end module c_loc_tests_7 -! { dg-final { cleanup-modules "c_loc_tests_7" } } diff --git a/gcc/testsuite/gfortran.dg/c_ptr_tests.f03 b/gcc/testsuite/gfortran.dg/c_ptr_tests.f03 index f0c9a3329d71..0b7c98be714a 100644 --- a/gcc/testsuite/gfortran.dg/c_ptr_tests.f03 +++ b/gcc/testsuite/gfortran.dg/c_ptr_tests.f03 @@ -42,5 +42,3 @@ module c_ptr_tests call c_f_pointer(self%myServices, localServices) end subroutine sub0 end module c_ptr_tests - -! { dg-final { cleanup-modules "c_ptr_tests" } } diff --git a/gcc/testsuite/gfortran.dg/c_ptr_tests_10.f03 b/gcc/testsuite/gfortran.dg/c_ptr_tests_10.f03 index fe416227594f..4ce1c6809e40 100644 --- a/gcc/testsuite/gfortran.dg/c_ptr_tests_10.f03 +++ b/gcc/testsuite/gfortran.dg/c_ptr_tests_10.f03 @@ -15,5 +15,3 @@ program main use c_ptr_tests_10 call sub0() end program main - -! { dg-final { cleanup-modules "c_ptr_tests_10" } } diff --git a/gcc/testsuite/gfortran.dg/c_ptr_tests_11.f03 b/gcc/testsuite/gfortran.dg/c_ptr_tests_11.f03 index 9448f82ba829..353a7956b9de 100644 --- a/gcc/testsuite/gfortran.dg/c_ptr_tests_11.f03 +++ b/gcc/testsuite/gfortran.dg/c_ptr_tests_11.f03 @@ -38,5 +38,3 @@ contains type(t), intent(out) :: a end subroutine func end module m -! { dg-final { cleanup-modules "fgsl m" } } - diff --git a/gcc/testsuite/gfortran.dg/c_ptr_tests_12.f03 b/gcc/testsuite/gfortran.dg/c_ptr_tests_12.f03 index 71e81709374d..d4ab175ca567 100644 --- a/gcc/testsuite/gfortran.dg/c_ptr_tests_12.f03 +++ b/gcc/testsuite/gfortran.dg/c_ptr_tests_12.f03 @@ -40,6 +40,3 @@ contains status = fgsl_vector_align(p_x, f_x) end subroutine expb_df end module tmod - -! { dg-final { cleanup-modules "fgsl tmod" } } - diff --git a/gcc/testsuite/gfortran.dg/c_ptr_tests_14.f90 b/gcc/testsuite/gfortran.dg/c_ptr_tests_14.f90 index c4101fb030e6..946c4dd96ab1 100644 --- a/gcc/testsuite/gfortran.dg/c_ptr_tests_14.f90 +++ b/gcc/testsuite/gfortran.dg/c_ptr_tests_14.f90 @@ -48,4 +48,3 @@ end program test ! { dg-final { scan-tree-dump-times "bbb =" 0 "original" } } ! { dg-final { cleanup-tree-dump "original" } } -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/c_ptr_tests_15.f90 b/gcc/testsuite/gfortran.dg/c_ptr_tests_15.f90 index 1ce0c15fdfd6..9959d62715ca 100644 --- a/gcc/testsuite/gfortran.dg/c_ptr_tests_15.f90 +++ b/gcc/testsuite/gfortran.dg/c_ptr_tests_15.f90 @@ -50,4 +50,3 @@ end program test ! { dg-final { scan-tree-dump-times "bbb =" 0 "original" } } ! { dg-final { cleanup-tree-dump "original" } } -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/c_ptr_tests_17.f90 b/gcc/testsuite/gfortran.dg/c_ptr_tests_17.f90 index 9bbd0dd41adc..05063471c0ab 100644 --- a/gcc/testsuite/gfortran.dg/c_ptr_tests_17.f90 +++ b/gcc/testsuite/gfortran.dg/c_ptr_tests_17.f90 @@ -84,5 +84,3 @@ function kill_C_FUNPTR() bind(C) end interface kill_C_FUNPTR = C_FUNLOC(fun) end function kill_C_FUNPTR - -! { dg-final { cleanup-modules "m3 m1" } } diff --git a/gcc/testsuite/gfortran.dg/c_ptr_tests_18.f90 b/gcc/testsuite/gfortran.dg/c_ptr_tests_18.f90 index 6239516ec2e8..ae6fd98b9121 100644 --- a/gcc/testsuite/gfortran.dg/c_ptr_tests_18.f90 +++ b/gcc/testsuite/gfortran.dg/c_ptr_tests_18.f90 @@ -31,5 +31,3 @@ program cfpointerstress write(*,*) 'ASSOCIATED =', associated(img) deallocate(r) end program cfpointerstress - -! { dg-final { cleanup-modules "nag_j_types" } } diff --git a/gcc/testsuite/gfortran.dg/c_ptr_tests_7.f03 b/gcc/testsuite/gfortran.dg/c_ptr_tests_7.f03 index 04cb8b22ab85..38768b141dfc 100644 --- a/gcc/testsuite/gfortran.dg/c_ptr_tests_7.f03 +++ b/gcc/testsuite/gfortran.dg/c_ptr_tests_7.f03 @@ -9,4 +9,3 @@ contains func0 = c_null_ptr end function func0 end module c_ptr_tests_7 -! { dg-final { cleanup-modules "c_ptr_tests_7" } } diff --git a/gcc/testsuite/gfortran.dg/c_ptr_tests_9.f03 b/gcc/testsuite/gfortran.dg/c_ptr_tests_9.f03 index f723492643f1..8fff5473e5d8 100644 --- a/gcc/testsuite/gfortran.dg/c_ptr_tests_9.f03 +++ b/gcc/testsuite/gfortran.dg/c_ptr_tests_9.f03 @@ -28,5 +28,3 @@ program main call sub0() end program main - -! { dg-final { cleanup-modules "c_ptr_tests_9" } } diff --git a/gcc/testsuite/gfortran.dg/c_size_t_test.f03 b/gcc/testsuite/gfortran.dg/c_size_t_test.f03 index 68064d78b07f..91d7aa57b053 100644 --- a/gcc/testsuite/gfortran.dg/c_size_t_test.f03 +++ b/gcc/testsuite/gfortran.dg/c_size_t_test.f03 @@ -14,5 +14,3 @@ contains end if end subroutine sub0 end module c_size_t_test - -! { dg-final { cleanup-modules "c_size_t_test" } } diff --git a/gcc/testsuite/gfortran.dg/char_array_constructor.f90 b/gcc/testsuite/gfortran.dg/char_array_constructor.f90 index 5f562e9fa68d..2cf3ae722c52 100644 --- a/gcc/testsuite/gfortran.dg/char_array_constructor.f90 +++ b/gcc/testsuite/gfortran.dg/char_array_constructor.f90 @@ -12,5 +12,3 @@ program y if (b(1) /= 'abcd ') call abort if (b(2) /= 'efghij') call abort end program y - -! { dg-final { cleanup-modules "z" } } diff --git a/gcc/testsuite/gfortran.dg/char_array_constructor_2.f90 b/gcc/testsuite/gfortran.dg/char_array_constructor_2.f90 index 766eb5290332..d6abc260caa4 100644 --- a/gcc/testsuite/gfortran.dg/char_array_constructor_2.f90 +++ b/gcc/testsuite/gfortran.dg/char_array_constructor_2.f90 @@ -11,4 +11,3 @@ end module foomod use foomod print *, aa, bb end -! { dg-final { cleanup-modules "foomod" } } diff --git a/gcc/testsuite/gfortran.dg/char_array_structure_constructor.f90 b/gcc/testsuite/gfortran.dg/char_array_structure_constructor.f90 index 22669363e0fc..cfe787b5375c 100644 --- a/gcc/testsuite/gfortran.dg/char_array_structure_constructor.f90 +++ b/gcc/testsuite/gfortran.dg/char_array_structure_constructor.f90 @@ -31,5 +31,3 @@ contains ENDDO end subroutine alloc END program char_array_structure_constructor - -! { dg-final { cleanup-modules "global" } } diff --git a/gcc/testsuite/gfortran.dg/char_length_13.f90 b/gcc/testsuite/gfortran.dg/char_length_13.f90 index 576d5be77755..dd5c05a85840 100644 --- a/gcc/testsuite/gfortran.dg/char_length_13.f90 +++ b/gcc/testsuite/gfortran.dg/char_length_13.f90 @@ -32,5 +32,3 @@ program main use bar call xmain() end program main - -! { dg-final { cleanup-modules "bar" } } diff --git a/gcc/testsuite/gfortran.dg/char_length_5.f90 b/gcc/testsuite/gfortran.dg/char_length_5.f90 index 03a4d8560297..929f01b22b43 100644 --- a/gcc/testsuite/gfortran.dg/char_length_5.f90 +++ b/gcc/testsuite/gfortran.dg/char_length_5.f90 @@ -58,4 +58,3 @@ program xjoin if (len (join (words2(2:4:2), sep2)) .ne. 10) call abort () end program xjoin -! { dg-final { cleanup-modules "util_mod" } } diff --git a/gcc/testsuite/gfortran.dg/char_length_7.f90 b/gcc/testsuite/gfortran.dg/char_length_7.f90 index 221c84090f83..d9c1b3874410 100644 --- a/gcc/testsuite/gfortran.dg/char_length_7.f90 +++ b/gcc/testsuite/gfortran.dg/char_length_7.f90 @@ -29,4 +29,3 @@ program xx ! This was another bug, uncovered when the PR was fixed. if (any(ccopy(z//mz(:)(i:j)) .ne. (/"zzgh ","zzjk "/))) call abort () end program xx -! { dg-final { cleanup-modules "str_mod" } } diff --git a/gcc/testsuite/gfortran.dg/char_length_9.f90 b/gcc/testsuite/gfortran.dg/char_length_9.f90 index dbec68cd8c39..36f724a0e0f8 100644 --- a/gcc/testsuite/gfortran.dg/char_length_9.f90 +++ b/gcc/testsuite/gfortran.dg/char_length_9.f90 @@ -18,5 +18,3 @@ CONTAINS val%c_val(i)(1:MIN (80, l_out-(i-1)*default_string_length)) END SUBROUTINE val_get END MODULE input_val_types - -! { dg-final { cleanup-modules "input_val_types" } } diff --git a/gcc/testsuite/gfortran.dg/char_result_11.f90 b/gcc/testsuite/gfortran.dg/char_result_11.f90 index 75e68f1ef464..c37b20eb75ae 100644 --- a/gcc/testsuite/gfortran.dg/char_result_11.f90 +++ b/gcc/testsuite/gfortran.dg/char_result_11.f90 @@ -113,5 +113,3 @@ program test print *, str end program test - -! { dg-final { cleanup-modules "cutils" } } diff --git a/gcc/testsuite/gfortran.dg/char_result_13.f90 b/gcc/testsuite/gfortran.dg/char_result_13.f90 index 741d55f166a9..638d6381e19b 100644 --- a/gcc/testsuite/gfortran.dg/char_result_13.f90 +++ b/gcc/testsuite/gfortran.dg/char_result_13.f90 @@ -45,5 +45,3 @@ end module abc use abc call xmain(3, 2) end -! { dg-final { cleanup-modules "abc" } } - diff --git a/gcc/testsuite/gfortran.dg/char_result_9.f90 b/gcc/testsuite/gfortran.dg/char_result_9.f90 index 062901e1bed4..e32df0e01b49 100644 --- a/gcc/testsuite/gfortran.dg/char_result_9.f90 +++ b/gcc/testsuite/gfortran.dg/char_result_9.f90 @@ -22,5 +22,3 @@ program huj s = s_to_c(c) end program huj - -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/character_assign_1.f90 b/gcc/testsuite/gfortran.dg/character_assign_1.f90 index a4e073299b31..02625ad5dc0b 100644 --- a/gcc/testsuite/gfortran.dg/character_assign_1.f90 +++ b/gcc/testsuite/gfortran.dg/character_assign_1.f90 @@ -14,4 +14,3 @@ CONTAINS TDA1L(NF1:NF2:NF1)%C = TDA1L(NF0+2:NF3:NF2/2)%C END SUBROUTINE END MODULE TESTS -! { dg-final { cleanup-modules "tests" } } diff --git a/gcc/testsuite/gfortran.dg/class_10.f03 b/gcc/testsuite/gfortran.dg/class_10.f03 index f238a597a65c..1e3b8547bb06 100644 --- a/gcc/testsuite/gfortran.dg/class_10.f03 +++ b/gcc/testsuite/gfortran.dg/class_10.f03 @@ -28,5 +28,3 @@ end module class(gradient_class), pointer :: g_initial, ip_save ip_save => g_initial%inner_product() ! ICE end - -! { dg-final { cleanup-modules "abstract_gradient" } } diff --git a/gcc/testsuite/gfortran.dg/class_12.f03 b/gcc/testsuite/gfortran.dg/class_12.f03 index 56c68a577872..312ca572de0b 100644 --- a/gcc/testsuite/gfortran.dg/class_12.f03 +++ b/gcc/testsuite/gfortran.dg/class_12.f03 @@ -41,5 +41,3 @@ contains operand = operand%product(scale) end subroutine end module - -! { dg-final { cleanup-modules "abstract_algebra" } } diff --git a/gcc/testsuite/gfortran.dg/class_13.f03 b/gcc/testsuite/gfortran.dg/class_13.f03 index 84073bf2276a..d83a85610483 100644 --- a/gcc/testsuite/gfortran.dg/class_13.f03 +++ b/gcc/testsuite/gfortran.dg/class_13.f03 @@ -34,4 +34,3 @@ contains end function end module concrete_inner_product -! { dg-final { cleanup-modules "concrete_vector concrete_gradient concrete_inner_product" } } diff --git a/gcc/testsuite/gfortran.dg/class_14.f03 b/gcc/testsuite/gfortran.dg/class_14.f03 index 4e6db17c960a..5116c661b9bb 100644 --- a/gcc/testsuite/gfortran.dg/class_14.f03 +++ b/gcc/testsuite/gfortran.dg/class_14.f03 @@ -50,5 +50,3 @@ module concrete_inner_product use concrete_gradient implicit none end module concrete_inner_product -! { dg-final { cleanup-modules "abstract_vector concrete_vector" } } -! { dg-final { cleanup-modules "concrete_gradient concrete_inner_product" } } diff --git a/gcc/testsuite/gfortran.dg/class_15.f03 b/gcc/testsuite/gfortran.dg/class_15.f03 index 4520a5996f97..1fc7ce4a2404 100644 --- a/gcc/testsuite/gfortran.dg/class_15.f03 +++ b/gcc/testsuite/gfortran.dg/class_15.f03 @@ -39,5 +39,3 @@ module mod_D use mod_A use mod_C end module - -! { dg-final { cleanup-modules "mod_a mod_b mod_c mod_d" } } diff --git a/gcc/testsuite/gfortran.dg/class_16.f03 b/gcc/testsuite/gfortran.dg/class_16.f03 index 7d0d38f80bdb..136097b41cd0 100644 --- a/gcc/testsuite/gfortran.dg/class_16.f03 +++ b/gcc/testsuite/gfortran.dg/class_16.f03 @@ -19,5 +19,3 @@ contains end function end module - -! { dg-final { cleanup-modules "m_rotation_matrix" } } diff --git a/gcc/testsuite/gfortran.dg/class_17.f03 b/gcc/testsuite/gfortran.dg/class_17.f03 index b015c1319f6a..0c5c23884d97 100644 --- a/gcc/testsuite/gfortran.dg/class_17.f03 +++ b/gcc/testsuite/gfortran.dg/class_17.f03 @@ -60,5 +60,3 @@ module b_module end type b_type end module b_module - -! { dg-final { cleanup-modules "error_stack_module b_module" } } diff --git a/gcc/testsuite/gfortran.dg/class_19.f03 b/gcc/testsuite/gfortran.dg/class_19.f03 index 27ee7b4e2cb4..63b8e06965a5 100644 --- a/gcc/testsuite/gfortran.dg/class_19.f03 +++ b/gcc/testsuite/gfortran.dg/class_19.f03 @@ -41,5 +41,3 @@ end program main ! { dg-final { scan-tree-dump-times "__builtin_free" 11 "original" } } ! { dg-final { cleanup-tree-dump "original" } } - -! { dg-final { cleanup-modules "foo_mod" } } diff --git a/gcc/testsuite/gfortran.dg/class_21.f03 b/gcc/testsuite/gfortran.dg/class_21.f03 index 93b9616aee9a..4a7135d3bba3 100644 --- a/gcc/testsuite/gfortran.dg/class_21.f03 +++ b/gcc/testsuite/gfortran.dg/class_21.f03 @@ -14,5 +14,3 @@ module m type(t),save :: default_t end module - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/class_22.f03 b/gcc/testsuite/gfortran.dg/class_22.f03 index df68783b4ab9..7e179f421584 100644 --- a/gcc/testsuite/gfortran.dg/class_22.f03 +++ b/gcc/testsuite/gfortran.dg/class_22.f03 @@ -27,5 +27,3 @@ contains end subroutine ice_proc end module ice_module - -! { dg-final { cleanup-modules "ice_module" } } diff --git a/gcc/testsuite/gfortran.dg/class_25.f03 b/gcc/testsuite/gfortran.dg/class_25.f03 index 3588b7759e57..4c3563ccb6d9 100644 --- a/gcc/testsuite/gfortran.dg/class_25.f03 +++ b/gcc/testsuite/gfortran.dg/class_25.f03 @@ -24,5 +24,3 @@ contains end module end - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/class_26.f03 b/gcc/testsuite/gfortran.dg/class_26.f03 index 629c9c98e4cc..ed4a2690cfd0 100644 --- a/gcc/testsuite/gfortran.dg/class_26.f03 +++ b/gcc/testsuite/gfortran.dg/class_26.f03 @@ -26,4 +26,3 @@ end module end -! { dg-final { cleanup-modules "s_mat_mod s_tester" } } diff --git a/gcc/testsuite/gfortran.dg/class_27.f03 b/gcc/testsuite/gfortran.dg/class_27.f03 index 3525dc467ba9..a3f2c882e212 100644 --- a/gcc/testsuite/gfortran.dg/class_27.f03 +++ b/gcc/testsuite/gfortran.dg/class_27.f03 @@ -63,5 +63,3 @@ module type1_type endif end function Type1_initProc end module type1_type - -! { dg-final { cleanup-modules "type2_type extended2a_type type1_type" } } diff --git a/gcc/testsuite/gfortran.dg/class_28.f03 b/gcc/testsuite/gfortran.dg/class_28.f03 index 684b8cdab766..258633df45be 100644 --- a/gcc/testsuite/gfortran.dg/class_28.f03 +++ b/gcc/testsuite/gfortran.dg/class_28.f03 @@ -41,5 +41,3 @@ program p allocate(x(1)) end program p - -! { dg-final { cleanup-modules "m m2" } } diff --git a/gcc/testsuite/gfortran.dg/class_29.f03 b/gcc/testsuite/gfortran.dg/class_29.f03 index d5ed8fae35c7..b27793f90897 100644 --- a/gcc/testsuite/gfortran.dg/class_29.f03 +++ b/gcc/testsuite/gfortran.dg/class_29.f03 @@ -30,5 +30,3 @@ allocate (t2 :: y) print *, x%a print *, y%b end - -! { dg-final { cleanup-modules "m1 m2" } } diff --git a/gcc/testsuite/gfortran.dg/class_32.f90 b/gcc/testsuite/gfortran.dg/class_32.f90 index b5857c1f645c..c388be42fc5d 100644 --- a/gcc/testsuite/gfortran.dg/class_32.f90 +++ b/gcc/testsuite/gfortran.dg/class_32.f90 @@ -37,5 +37,3 @@ END MODULE PROGRAM p USE m END - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/class_33.f90 b/gcc/testsuite/gfortran.dg/class_33.f90 index 7c3c197262a6..c2bd4e429368 100644 --- a/gcc/testsuite/gfortran.dg/class_33.f90 +++ b/gcc/testsuite/gfortran.dg/class_33.f90 @@ -9,5 +9,3 @@ module Molecular_Abundances_Structure end type class(molecularAbundancesStructure), pointer :: molecules end module - -! { dg-final { cleanup-modules "molecular_abundances_structure" } } diff --git a/gcc/testsuite/gfortran.dg/class_34.f90 b/gcc/testsuite/gfortran.dg/class_34.f90 index ecdb4ddc8022..3375396aa6e8 100644 --- a/gcc/testsuite/gfortran.dg/class_34.f90 +++ b/gcc/testsuite/gfortran.dg/class_34.f90 @@ -20,5 +20,3 @@ module m2 end module end - -! { dg-final { cleanup-modules "m0 m1 m2" } } diff --git a/gcc/testsuite/gfortran.dg/class_35.f90 b/gcc/testsuite/gfortran.dg/class_35.f90 index 1b5502a78703..87a5c871294a 100644 --- a/gcc/testsuite/gfortran.dg/class_35.f90 +++ b/gcc/testsuite/gfortran.dg/class_35.f90 @@ -22,5 +22,3 @@ class(three), allocatable :: a2 if (same_type_as(a1,a2)) call abort() end - -! { dg-final { cleanup-modules "one one_two" } } diff --git a/gcc/testsuite/gfortran.dg/class_37.f03 b/gcc/testsuite/gfortran.dg/class_37.f03 index e3ff8ce8d02c..1d75999626f0 100644 --- a/gcc/testsuite/gfortran.dg/class_37.f03 +++ b/gcc/testsuite/gfortran.dg/class_37.f03 @@ -259,5 +259,3 @@ subroutine psb_cdall(ictxt, desc, info,mg,ng,vg,vl,flag,nl,repl, globalcheck) return end subroutine psb_cdall - -! { dg-final { cleanup-modules "psb_penv_mod psb_indx_map_mod psb_gen_block_map_mod psb_descriptor_type psb_cd_if_tools_mod psb_cd_tools_mod psb_base_tools_mod" } } diff --git a/gcc/testsuite/gfortran.dg/class_40.f03 b/gcc/testsuite/gfortran.dg/class_40.f03 index dde1acdc32ed..b6214a9e6084 100644 --- a/gcc/testsuite/gfortran.dg/class_40.f03 +++ b/gcc/testsuite/gfortran.dg/class_40.f03 @@ -32,5 +32,3 @@ program test type(treeNode) :: node call walk (node) end program - -! { dg-final { cleanup-modules "tree_nodes merger_trees merger_tree_build" } } diff --git a/gcc/testsuite/gfortran.dg/class_41.f03 b/gcc/testsuite/gfortran.dg/class_41.f03 index bcab2b4ceef6..5c24fe1be511 100644 --- a/gcc/testsuite/gfortran.dg/class_41.f03 +++ b/gcc/testsuite/gfortran.dg/class_41.f03 @@ -20,5 +20,3 @@ contains print *,a_string(this) end subroutine b_sub end module a_module - -! { dg-final { cleanup-modules "a_module" } } diff --git a/gcc/testsuite/gfortran.dg/class_42.f03 b/gcc/testsuite/gfortran.dg/class_42.f03 index cd3047fb88f5..10acf3bd8b83 100644 --- a/gcc/testsuite/gfortran.dg/class_42.f03 +++ b/gcc/testsuite/gfortran.dg/class_42.f03 @@ -12,5 +12,3 @@ contains class(Overload_AnException_impl_t) :: self end subroutine end module - -! { dg-final { cleanup-modules "overload_anexception_impl" } } diff --git a/gcc/testsuite/gfortran.dg/class_45b.f03 b/gcc/testsuite/gfortran.dg/class_45b.f03 index ed0d67435c14..5c047e2c5987 100644 --- a/gcc/testsuite/gfortran.dg/class_45b.f03 +++ b/gcc/testsuite/gfortran.dg/class_45b.f03 @@ -10,5 +10,3 @@ program Test class(t0), allocatable :: c allocate(t1 :: c) end program Test - -! { dg-final { cleanup-modules "G_Nodes" } } diff --git a/gcc/testsuite/gfortran.dg/class_46.f03 b/gcc/testsuite/gfortran.dg/class_46.f03 index 4719c252f636..ef718db25d46 100644 --- a/gcc/testsuite/gfortran.dg/class_46.f03 +++ b/gcc/testsuite/gfortran.dg/class_46.f03 @@ -14,5 +14,3 @@ use m implicit none if (allocated(x)) call abort() end - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/class_47.f90 b/gcc/testsuite/gfortran.dg/class_47.f90 index 90a7560bc5ee..56f342e07645 100644 --- a/gcc/testsuite/gfortran.dg/class_47.f90 +++ b/gcc/testsuite/gfortran.dg/class_47.f90 @@ -36,5 +36,3 @@ PROGRAM main call test(sparseMatrix) END PROGRAM - -! { dg-final { cleanup-modules "m_sparsematrix m_subroutine" } } diff --git a/gcc/testsuite/gfortran.dg/class_9.f03 b/gcc/testsuite/gfortran.dg/class_9.f03 index 5dbd4597abd1..0e6509c0503b 100644 --- a/gcc/testsuite/gfortran.dg/class_9.f03 +++ b/gcc/testsuite/gfortran.dg/class_9.f03 @@ -65,4 +65,3 @@ end allocate(x) call s (x) end -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/class_allocate_10.f03 b/gcc/testsuite/gfortran.dg/class_allocate_10.f03 index d3afa395ec9f..2e4f3b8aa39a 100644 --- a/gcc/testsuite/gfortran.dg/class_allocate_10.f03 +++ b/gcc/testsuite/gfortran.dg/class_allocate_10.f03 @@ -60,5 +60,3 @@ program main type is (integrand); if (any (kernel1%variable .ne. [3,4,5])) call abort end select end program -! { dg-final { cleanup-modules "show_producer_class" } } - diff --git a/gcc/testsuite/gfortran.dg/class_allocate_11.f03 b/gcc/testsuite/gfortran.dg/class_allocate_11.f03 index e36e810aba82..b8422c0f9f42 100644 --- a/gcc/testsuite/gfortran.dg/class_allocate_11.f03 +++ b/gcc/testsuite/gfortran.dg/class_allocate_11.f03 @@ -58,5 +58,3 @@ program prog end if end select end program prog -! { dg-final { cleanup-modules "generic_deferred" } } - diff --git a/gcc/testsuite/gfortran.dg/class_allocate_12.f90 b/gcc/testsuite/gfortran.dg/class_allocate_12.f90 index 2dce84e6133b..d50943d5e447 100644 --- a/gcc/testsuite/gfortran.dg/class_allocate_12.f90 +++ b/gcc/testsuite/gfortran.dg/class_allocate_12.f90 @@ -88,5 +88,3 @@ program main attractor = constructor( [1., 1., 1.] , timed_lorenz_integrator) call integrate(attractor) end program main - -! { dg-final { cleanup-modules "surrogate_module strategy_module integrand_module runge_kutta_2nd_module" } } diff --git a/gcc/testsuite/gfortran.dg/class_allocate_7.f03 b/gcc/testsuite/gfortran.dg/class_allocate_7.f03 index ddab4073dec9..ee01faddf44f 100644 --- a/gcc/testsuite/gfortran.dg/class_allocate_7.f03 +++ b/gcc/testsuite/gfortran.dg/class_allocate_7.f03 @@ -31,5 +31,3 @@ program main allocate(kernel,source=executive_producer%create_show ()) if (kernel%variable .ne. 99) call abort end program -! { dg-final { cleanup-modules "show_producer_class" } } - diff --git a/gcc/testsuite/gfortran.dg/class_allocate_8.f03 b/gcc/testsuite/gfortran.dg/class_allocate_8.f03 index 85094ad1fe07..1abc55776f86 100644 --- a/gcc/testsuite/gfortran.dg/class_allocate_8.f03 +++ b/gcc/testsuite/gfortran.dg/class_allocate_8.f03 @@ -49,5 +49,3 @@ program main type is (integrand); if (any (kernel%variable .ne. -1)) call abort end select end program -! { dg-final { cleanup-modules "show_producer_class" } } - diff --git a/gcc/testsuite/gfortran.dg/class_allocate_9.f03 b/gcc/testsuite/gfortran.dg/class_allocate_9.f03 index 2446ed61413e..0c7b1f79cefe 100644 --- a/gcc/testsuite/gfortran.dg/class_allocate_9.f03 +++ b/gcc/testsuite/gfortran.dg/class_allocate_9.f03 @@ -32,5 +32,3 @@ program main if (kernel1%variable .ne. -1) call abort if (kernel2%variable .ne. -1) call abort end program -! { dg-final { cleanup-modules "show_producer_class" } } - diff --git a/gcc/testsuite/gfortran.dg/class_array_12.f03 b/gcc/testsuite/gfortran.dg/class_array_12.f03 index 2a1e440636ef..9873db7b0bd5 100644 --- a/gcc/testsuite/gfortran.dg/class_array_12.f03 +++ b/gcc/testsuite/gfortran.dg/class_array_12.f03 @@ -29,5 +29,3 @@ contains end function BGet end module test - -! { dg-final { cleanup-modules "test" } } diff --git a/gcc/testsuite/gfortran.dg/class_array_3.f03 b/gcc/testsuite/gfortran.dg/class_array_3.f03 index 8972161fbb3f..6db375c9425b 100644 --- a/gcc/testsuite/gfortran.dg/class_array_3.f03 +++ b/gcc/testsuite/gfortran.dg/class_array_3.f03 @@ -136,5 +136,3 @@ program main ! print *, "After qsort: ", A%disp() if (any (A%disp() .ne. [2,3,4,5,7])) call abort end program main - -! { dg-final { cleanup-modules "m_qsort test" } } diff --git a/gcc/testsuite/gfortran.dg/class_array_4.f03 b/gcc/testsuite/gfortran.dg/class_array_4.f03 index 7c748f008d06..46b254db676e 100644 --- a/gcc/testsuite/gfortran.dg/class_array_4.f03 +++ b/gcc/testsuite/gfortran.dg/class_array_4.f03 @@ -23,4 +23,3 @@ end module m call x(:)%foo(n) if (any(n .ne. [99,199,299])) call abort end -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/class_array_5.f03 b/gcc/testsuite/gfortran.dg/class_array_5.f03 index 2a7e2f1bc467..740a0d4f2715 100644 --- a/gcc/testsuite/gfortran.dg/class_array_5.f03 +++ b/gcc/testsuite/gfortran.dg/class_array_5.f03 @@ -22,4 +22,3 @@ module ice6 end subroutine do_something_else end module ice6 -! { dg-final { cleanup-modules "ice6" } } diff --git a/gcc/testsuite/gfortran.dg/class_array_6.f03 b/gcc/testsuite/gfortran.dg/class_array_6.f03 index 4f8b803befbf..ab4766f9d0d2 100644 --- a/gcc/testsuite/gfortran.dg/class_array_6.f03 +++ b/gcc/testsuite/gfortran.dg/class_array_6.f03 @@ -30,4 +30,3 @@ CONTAINS !TYPE(ParentVector), INTENT(INOUT) :: pvec END SUBROUTINE item_operation END MODULE procedure_intent_nonsense -! { dg-final { cleanup-modules "procedure_intent_nonsense" } } diff --git a/gcc/testsuite/gfortran.dg/class_array_7.f03 b/gcc/testsuite/gfortran.dg/class_array_7.f03 index 225cc7e06c88..435e6f52ee61 100644 --- a/gcc/testsuite/gfortran.dg/class_array_7.f03 +++ b/gcc/testsuite/gfortran.dg/class_array_7.f03 @@ -55,5 +55,3 @@ program main call reallocate (a) if (trim (print_type ("a", a)) .ne. "a is base_type") call abort end program main - -! { dg-final { cleanup-modules "realloc" } } diff --git a/gcc/testsuite/gfortran.dg/class_array_9.f03 b/gcc/testsuite/gfortran.dg/class_array_9.f03 index 6b07aeac4d9f..c771c61a1299 100644 --- a/gcc/testsuite/gfortran.dg/class_array_9.f03 +++ b/gcc/testsuite/gfortran.dg/class_array_9.f03 @@ -42,5 +42,3 @@ end module if (x(4)%disp () .ne. 4) call abort end - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/class_defined_operator_1.f03 b/gcc/testsuite/gfortran.dg/class_defined_operator_1.f03 index 0b878f201490..008739e3f988 100644 --- a/gcc/testsuite/gfortran.dg/class_defined_operator_1.f03 +++ b/gcc/testsuite/gfortran.dg/class_defined_operator_1.f03 @@ -100,5 +100,3 @@ contains this = this*scale end subroutine end program - -! { dg-final { cleanup-modules "bar_module foo_module" } } diff --git a/gcc/testsuite/gfortran.dg/class_dummy_2.f03 b/gcc/testsuite/gfortran.dg/class_dummy_2.f03 index c1735822bb45..2078cd7a662a 100644 --- a/gcc/testsuite/gfortran.dg/class_dummy_2.f03 +++ b/gcc/testsuite/gfortran.dg/class_dummy_2.f03 @@ -29,5 +29,3 @@ contains end module fails_test end - -! { dg-final { cleanup-modules "fails_mod fails_test" } } diff --git a/gcc/testsuite/gfortran.dg/class_result_1.f03 b/gcc/testsuite/gfortran.dg/class_result_1.f03 index f1f542bb1219..011878e95871 100644 --- a/gcc/testsuite/gfortran.dg/class_result_1.f03 +++ b/gcc/testsuite/gfortran.dg/class_result_1.f03 @@ -58,5 +58,3 @@ program random_walk end do end program random_walk - -! { dg-final { cleanup-modules "points2d" } } diff --git a/gcc/testsuite/gfortran.dg/class_to_type_2.f90 b/gcc/testsuite/gfortran.dg/class_to_type_2.f90 index 75c2a887612b..e6181a4d337f 100644 --- a/gcc/testsuite/gfortran.dg/class_to_type_2.f90 +++ b/gcc/testsuite/gfortran.dg/class_to_type_2.f90 @@ -93,5 +93,3 @@ program prog call subpr2_array (g ()) end program - -! { dg-final { cleanup-modules "mod_subpr" } } diff --git a/gcc/testsuite/gfortran.dg/coarray/registering_1.f90 b/gcc/testsuite/gfortran.dg/coarray/registering_1.f90 index c6bcf92c18f3..a18ba615af73 100644 --- a/gcc/testsuite/gfortran.dg/coarray/registering_1.f90 +++ b/gcc/testsuite/gfortran.dg/coarray/registering_1.f90 @@ -39,5 +39,3 @@ contains if (not_refed /= 784) call abort() end subroutine uncalled end subroutine test - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/coarray_14.f90 b/gcc/testsuite/gfortran.dg/coarray_14.f90 index 49188d60e155..3097eede7571 100644 --- a/gcc/testsuite/gfortran.dg/coarray_14.f90 +++ b/gcc/testsuite/gfortran.dg/coarray_14.f90 @@ -51,5 +51,3 @@ type(t), allocatable :: a[:] allocate (t :: a) ! { dg-error "Coarray specification required in ALLOCATE statement" } allocate (t :: a[*]) ! OK end program myTest - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/coarray_19.f90 b/gcc/testsuite/gfortran.dg/coarray_19.f90 index cbb1dd20d8f4..637750a6121e 100644 --- a/gcc/testsuite/gfortran.dg/coarray_19.f90 +++ b/gcc/testsuite/gfortran.dg/coarray_19.f90 @@ -23,5 +23,3 @@ end module m ! as->cotype was not AS_DEFERERED. use m end - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/coarray_21.f90 b/gcc/testsuite/gfortran.dg/coarray_21.f90 index 8aa0aa6c5a66..e805cf68a0f0 100644 --- a/gcc/testsuite/gfortran.dg/coarray_21.f90 +++ b/gcc/testsuite/gfortran.dg/coarray_21.f90 @@ -22,6 +22,3 @@ program test type(pct) :: picture[*] allocate(picture%data(size, size)) end program test - - -! { dg-final { cleanup-modules "mod_reduction" } } diff --git a/gcc/testsuite/gfortran.dg/coarray_6.f90 b/gcc/testsuite/gfortran.dg/coarray_6.f90 index d3c600b36189..9fb06d4680a9 100644 --- a/gcc/testsuite/gfortran.dg/coarray_6.f90 +++ b/gcc/testsuite/gfortran.dg/coarray_6.f90 @@ -81,5 +81,3 @@ end subroutine valid program main integer :: A[*] ! Valid, implicit SAVE attribute end program main - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/coarray_8.f90 b/gcc/testsuite/gfortran.dg/coarray_8.f90 index 6ceba8b9a95a..6defc1aad6ab 100644 --- a/gcc/testsuite/gfortran.dg/coarray_8.f90 +++ b/gcc/testsuite/gfortran.dg/coarray_8.f90 @@ -187,5 +187,3 @@ subroutine assign42() integer, allocatable :: z(:)[:] z(:)[1] = z end subroutine assign42 - -! { dg-final { cleanup-modules "mod2 m mmm3 mmm4" } } diff --git a/gcc/testsuite/gfortran.dg/coarray_args_2.f90 b/gcc/testsuite/gfortran.dg/coarray_args_2.f90 index 66a5a921c66e..c7dc490cc470 100644 --- a/gcc/testsuite/gfortran.dg/coarray_args_2.f90 +++ b/gcc/testsuite/gfortran.dg/coarray_args_2.f90 @@ -46,5 +46,3 @@ program rank_mismatch_02 write(*, *) 'OK' end if end program - -! { dg-final { cleanup-modules "mod_rank_mismatch_02" } } diff --git a/gcc/testsuite/gfortran.dg/coarray_lib_token_2.f90 b/gcc/testsuite/gfortran.dg/coarray_lib_token_2.f90 index 063115470119..fe4df3b0da63 100644 --- a/gcc/testsuite/gfortran.dg/coarray_lib_token_2.f90 +++ b/gcc/testsuite/gfortran.dg/coarray_lib_token_2.f90 @@ -113,4 +113,3 @@ end program main ! { dg-final { scan-tree-dump-times "sub_opt \\(.integer.kind=4. .. caf.data, caf.token, 0\\)" 1 "original" } } ! ! { dg-final { cleanup-tree-dump "original" } } -! { dg-final { cleanup-modules "matrix_data" } } diff --git a/gcc/testsuite/gfortran.dg/coarray_lock_3.f90 b/gcc/testsuite/gfortran.dg/coarray_lock_3.f90 index 958cee4c09ee..388857307f05 100644 --- a/gcc/testsuite/gfortran.dg/coarray_lock_3.f90 +++ b/gcc/testsuite/gfortran.dg/coarray_lock_3.f90 @@ -113,5 +113,3 @@ contains type(lock_type), intent(in) :: x[*] end subroutine test end subroutine argument_check - -! { dg-final { cleanup-modules "m m2 m3" } } diff --git a/gcc/testsuite/gfortran.dg/coarray_lock_5.f90 b/gcc/testsuite/gfortran.dg/coarray_lock_5.f90 index aac90279854b..b419606b0de1 100644 --- a/gcc/testsuite/gfortran.dg/coarray_lock_5.f90 +++ b/gcc/testsuite/gfortran.dg/coarray_lock_5.f90 @@ -49,5 +49,3 @@ subroutine test2() integer, allocatable :: d[:] ! { dg-error "Noncoarray component c at .1. of type LOCK_TYPE or with subcomponent of type LOCK_TYPE must have a codimension or be a subcomponent of a coarray. .Variables of type t5 may not have a codimension as d at .2. has a codimension or a coarray subcomponent." } end type t5 end subroutine test2 - -! { dg-final { cleanup-modules "m3" } } diff --git a/gcc/testsuite/gfortran.dg/com_block_driver.f90 b/gcc/testsuite/gfortran.dg/com_block_driver.f90 index 691a40fe59d1..0445635c8816 100644 --- a/gcc/testsuite/gfortran.dg/com_block_driver.f90 +++ b/gcc/testsuite/gfortran.dg/com_block_driver.f90 @@ -32,5 +32,3 @@ program comBlockDriver call testTypes() end program comBlockDriver - -! { dg-final { cleanup-modules "mycommodule comblocktests" } } diff --git a/gcc/testsuite/gfortran.dg/common_12.f90 b/gcc/testsuite/gfortran.dg/common_12.f90 index 0eea80f03b86..39082f8931b4 100644 --- a/gcc/testsuite/gfortran.dg/common_12.f90 +++ b/gcc/testsuite/gfortran.dg/common_12.f90 @@ -14,5 +14,3 @@ contains call bar(z0) end subroutine foo end module - -! { dg-final { cleanup-modules "pr39594" } } diff --git a/gcc/testsuite/gfortran.dg/common_14.f90 b/gcc/testsuite/gfortran.dg/common_14.f90 index 892e4a5705f3..911d695e15bc 100644 --- a/gcc/testsuite/gfortran.dg/common_14.f90 +++ b/gcc/testsuite/gfortran.dg/common_14.f90 @@ -24,5 +24,3 @@ end call two() end - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/common_17.f90 b/gcc/testsuite/gfortran.dg/common_17.f90 index 8ac21e7afda8..bc9602dd9f6f 100644 --- a/gcc/testsuite/gfortran.dg/common_17.f90 +++ b/gcc/testsuite/gfortran.dg/common_17.f90 @@ -8,4 +8,3 @@ module foo integer:: a, b common a end module foo -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/complex_intrinsic_5.f90 b/gcc/testsuite/gfortran.dg/complex_intrinsic_5.f90 index 49b8eaaa68e8..1f76f0ad054f 100644 --- a/gcc/testsuite/gfortran.dg/complex_intrinsic_5.f90 +++ b/gcc/testsuite/gfortran.dg/complex_intrinsic_5.f90 @@ -217,5 +217,3 @@ PROGRAM ArcTrigHyp call check(atanh(z4), cmplx(-0.38187020129010862908881230531688930_4, -1.07198475450905931839240655913126728_4, kind=4)) call check(atanh(z8), cmplx(-0.38187020129010862908881230531688930_8, -1.07198475450905931839240655913126728_8, kind=8)) END PROGRAM ArcTrigHyp - -! { dg-final { cleanup-modules "test" } } diff --git a/gcc/testsuite/gfortran.dg/constructor_1.f90 b/gcc/testsuite/gfortran.dg/constructor_1.f90 index e8fe03ac38c4..7b995f52b197 100644 --- a/gcc/testsuite/gfortran.dg/constructor_1.f90 +++ b/gcc/testsuite/gfortran.dg/constructor_1.f90 @@ -38,5 +38,3 @@ program myuse c = mycomplex(x=0.0, y=1.0) ! A function reference c = mycomplex(0.0, 1.0) ! A function reference end program myuse - -! { dg-final { cleanup-modules "mycomplex_module" } } diff --git a/gcc/testsuite/gfortran.dg/constructor_3.f90 b/gcc/testsuite/gfortran.dg/constructor_3.f90 index 4015090bced7..badff3f6af5d 100644 --- a/gcc/testsuite/gfortran.dg/constructor_3.f90 +++ b/gcc/testsuite/gfortran.dg/constructor_3.f90 @@ -43,5 +43,3 @@ if (k /= 42) call abort () !print *, x%j !print *, k end - -! { dg-final { cleanup-modules "m m2" } } diff --git a/gcc/testsuite/gfortran.dg/constructor_5.f90 b/gcc/testsuite/gfortran.dg/constructor_5.f90 index ab9c9f2f5e3f..197e082fed5a 100644 --- a/gcc/testsuite/gfortran.dg/constructor_5.f90 +++ b/gcc/testsuite/gfortran.dg/constructor_5.f90 @@ -30,5 +30,3 @@ contains type(t2) :: f2 end function end module - -! { dg-final { cleanup-modules "m m2" } } diff --git a/gcc/testsuite/gfortran.dg/constructor_6.f90 b/gcc/testsuite/gfortran.dg/constructor_6.f90 index 00b99f2eba63..84b6f375c39c 100644 --- a/gcc/testsuite/gfortran.dg/constructor_6.f90 +++ b/gcc/testsuite/gfortran.dg/constructor_6.f90 @@ -167,5 +167,3 @@ program Struct_over if (my_test_cnt /= 6) call abort() end program Struct_over - -! { dg-final { cleanup-modules "test_cnt rational temp_node" } } diff --git a/gcc/testsuite/gfortran.dg/contained_1.f90 b/gcc/testsuite/gfortran.dg/contained_1.f90 index 05216b2285a9..9b6e4395492d 100644 --- a/gcc/testsuite/gfortran.dg/contained_1.f90 +++ b/gcc/testsuite/gfortran.dg/contained_1.f90 @@ -31,5 +31,3 @@ program contained_1 call a if (i .ne. 1) call abort end program - -! { dg-final { cleanup-modules "contained_1_mod" } } diff --git a/gcc/testsuite/gfortran.dg/contained_3.f90 b/gcc/testsuite/gfortran.dg/contained_3.f90 index 5ae41597c037..d5543a149f01 100644 --- a/gcc/testsuite/gfortran.dg/contained_3.f90 +++ b/gcc/testsuite/gfortran.dg/contained_3.f90 @@ -46,5 +46,3 @@ END PROGRAM test INTEGER FUNCTION setbd() setbd=42 END FUNCTION setbd - -! { dg-final { cleanup-modules "ksbin1_aux_mod" } } diff --git a/gcc/testsuite/gfortran.dg/contained_module_proc_1.f90 b/gcc/testsuite/gfortran.dg/contained_module_proc_1.f90 index a1e58929378b..a6c2462f64a5 100644 --- a/gcc/testsuite/gfortran.dg/contained_module_proc_1.f90 +++ b/gcc/testsuite/gfortran.dg/contained_module_proc_1.f90 @@ -36,5 +36,3 @@ program fire implicit none if(.not. is_gfortran()) call abort() end program fire -! { dg-final { cleanup-modules "chk_gfortran" } } - diff --git a/gcc/testsuite/gfortran.dg/contains_empty_2.f03 b/gcc/testsuite/gfortran.dg/contains_empty_2.f03 index 62e18f43d14e..b530d89d7042 100644 --- a/gcc/testsuite/gfortran.dg/contains_empty_2.f03 +++ b/gcc/testsuite/gfortran.dg/contains_empty_2.f03 @@ -10,5 +10,3 @@ module truc integer, parameter :: answer = 42 contains end module truc - -! { dg-final { cleanup-modules "truc" } } diff --git a/gcc/testsuite/gfortran.dg/convert_1.f90 b/gcc/testsuite/gfortran.dg/convert_1.f90 index 97ebc65bc722..0723cd012f18 100644 --- a/gcc/testsuite/gfortran.dg/convert_1.f90 +++ b/gcc/testsuite/gfortran.dg/convert_1.f90 @@ -14,5 +14,3 @@ USE MODULE_A USE MODULE_B a = 0 END - -! { dg-final { cleanup-modules "module_a module_b" } } diff --git a/gcc/testsuite/gfortran.dg/cray_pointers_5.f90 b/gcc/testsuite/gfortran.dg/cray_pointers_5.f90 index 21081194bcff..76bb9791b8ae 100644 --- a/gcc/testsuite/gfortran.dg/cray_pointers_5.f90 +++ b/gcc/testsuite/gfortran.dg/cray_pointers_5.f90 @@ -13,5 +13,3 @@ end module cray_pointers_5 ipt = loc (arr) if (any (var .ne. (/1, 2, 3, 4, 5, 6, 7, 8, 9, 10/))) call abort end - -! { dg-final { cleanup-modules "cray_pointers_5" } } diff --git a/gcc/testsuite/gfortran.dg/cray_pointers_9.f90 b/gcc/testsuite/gfortran.dg/cray_pointers_9.f90 index 81bcb199a1ef..cdcd56f68fae 100644 --- a/gcc/testsuite/gfortran.dg/cray_pointers_9.f90 +++ b/gcc/testsuite/gfortran.dg/cray_pointers_9.f90 @@ -101,4 +101,3 @@ program fptr p = transfer(fp,p) write(*,'(a)') fun([1,2,3]) end program fptr -! { dg-final { cleanup-modules "funcs other_fun" } } diff --git a/gcc/testsuite/gfortran.dg/data_constraints_1.f90 b/gcc/testsuite/gfortran.dg/data_constraints_1.f90 index bcf23ba34acf..5f11ffdbaea5 100644 --- a/gcc/testsuite/gfortran.dg/data_constraints_1.f90 +++ b/gcc/testsuite/gfortran.dg/data_constraints_1.f90 @@ -28,5 +28,3 @@ contains data foobar /0/ ! { dg-error "conflicts with FUNCTION" } end function foobar end - -! { dg-final { cleanup-modules "global" } } diff --git a/gcc/testsuite/gfortran.dg/data_namelist_conflict.f90 b/gcc/testsuite/gfortran.dg/data_namelist_conflict.f90 index b09f167fc7c7..177553c716e0 100644 --- a/gcc/testsuite/gfortran.dg/data_namelist_conflict.f90 +++ b/gcc/testsuite/gfortran.dg/data_namelist_conflict.f90 @@ -23,4 +23,3 @@ program test if (i /= 0 .or. j /= 1) call abort close(10) end program -! { dg-final { cleanup-modules "globals" } } diff --git a/gcc/testsuite/gfortran.dg/default_format_1.f90 b/gcc/testsuite/gfortran.dg/default_format_1.f90 index e374f1b895dd..e439f9bb6d0f 100644 --- a/gcc/testsuite/gfortran.dg/default_format_1.f90 +++ b/gcc/testsuite/gfortran.dg/default_format_1.f90 @@ -24,4 +24,3 @@ program main if (test (-huge(0.0_8), 1) /= 0) call abort end program main ! -! { dg-final { cleanup-modules "test_default_format" } } diff --git a/gcc/testsuite/gfortran.dg/default_format_2.f90 b/gcc/testsuite/gfortran.dg/default_format_2.f90 index 264246732203..e970090aa1d5 100644 --- a/gcc/testsuite/gfortran.dg/default_format_2.f90 +++ b/gcc/testsuite/gfortran.dg/default_format_2.f90 @@ -20,4 +20,3 @@ program main if (test (-huge(0.0_kl), 1) /= 0) call abort end program main ! -! { dg-final { cleanup-modules "test_default_format" } } diff --git a/gcc/testsuite/gfortran.dg/default_format_denormal_1.f90 b/gcc/testsuite/gfortran.dg/default_format_denormal_1.f90 index 7c9605383768..743a89498692 100644 --- a/gcc/testsuite/gfortran.dg/default_format_denormal_1.f90 +++ b/gcc/testsuite/gfortran.dg/default_format_denormal_1.f90 @@ -23,4 +23,3 @@ program main end program main ! -! { dg-final { cleanup-modules "test_default_format" } } diff --git a/gcc/testsuite/gfortran.dg/default_format_denormal_2.f90 b/gcc/testsuite/gfortran.dg/default_format_denormal_2.f90 index 36697067c7f8..a5337ca3b9e2 100644 --- a/gcc/testsuite/gfortran.dg/default_format_denormal_2.f90 +++ b/gcc/testsuite/gfortran.dg/default_format_denormal_2.f90 @@ -18,4 +18,3 @@ program main if (test (-tiny(0.0_kl), 1) /= 0) call abort end program main ! -! { dg-final { cleanup-modules "test_default_format" } } diff --git a/gcc/testsuite/gfortran.dg/default_initialization_1.f90 b/gcc/testsuite/gfortran.dg/default_initialization_1.f90 index b03b698f5cc4..6a76feb9f267 100644 --- a/gcc/testsuite/gfortran.dg/default_initialization_1.f90 +++ b/gcc/testsuite/gfortran.dg/default_initialization_1.f90 @@ -17,5 +17,3 @@ module bad end type default_initialization type (default_initialization) t ! { dg-error "default initialization" } end module bad - -! { dg-final { cleanup-modules "bad" } } diff --git a/gcc/testsuite/gfortran.dg/default_initialization_2.f90 b/gcc/testsuite/gfortran.dg/default_initialization_2.f90 index cc7ecdc4061d..d3595ee909de 100644 --- a/gcc/testsuite/gfortran.dg/default_initialization_2.f90 +++ b/gcc/testsuite/gfortran.dg/default_initialization_2.f90 @@ -32,5 +32,3 @@ TYPE(BLOCK) MATRIX POINTER MATRIX ALLOCATE(MATRIX) END - -! { dg-final { cleanup-modules "mat" } } diff --git a/gcc/testsuite/gfortran.dg/default_initialization_3.f90 b/gcc/testsuite/gfortran.dg/default_initialization_3.f90 index 720b35523ebe..e0bd63d004df 100644 --- a/gcc/testsuite/gfortran.dg/default_initialization_3.f90 +++ b/gcc/testsuite/gfortran.dg/default_initialization_3.f90 @@ -105,4 +105,3 @@ END call other call dominique end -! { dg-final { cleanup-modules "demo m1" } } diff --git a/gcc/testsuite/gfortran.dg/default_initialization_4.f90 b/gcc/testsuite/gfortran.dg/default_initialization_4.f90 index 7a15ba2c375f..b65020f18779 100644 --- a/gcc/testsuite/gfortran.dg/default_initialization_4.f90 +++ b/gcc/testsuite/gfortran.dg/default_initialization_4.f90 @@ -19,4 +19,3 @@ if (t%x /= 42) call abort() t%x = 0 if (t%x /= 0) call abort() end -! { dg-final { cleanup-modules "good" } } diff --git a/gcc/testsuite/gfortran.dg/default_initialization_5.f90 b/gcc/testsuite/gfortran.dg/default_initialization_5.f90 index 11927619db4b..b32dae7c6cb0 100644 --- a/gcc/testsuite/gfortran.dg/default_initialization_5.f90 +++ b/gcc/testsuite/gfortran.dg/default_initialization_5.f90 @@ -63,4 +63,3 @@ end program ! { dg-final { scan-tree-dump-times "my_data.head = 0B" 1 "original" } } ! { dg-final { scan-tree-dump-times "my_data.head = &tgt" 1 "original" } } ! { dg-final { cleanup-tree-dump "original" } } -! { dg-final { cleanup-modules "arr_m list_m worker_mod" } } diff --git a/gcc/testsuite/gfortran.dg/defined_operators_1.f90 b/gcc/testsuite/gfortran.dg/defined_operators_1.f90 index c7868d14c6cc..9d9901853d3a 100644 --- a/gcc/testsuite/gfortran.dg/defined_operators_1.f90 +++ b/gcc/testsuite/gfortran.dg/defined_operators_1.f90 @@ -65,4 +65,3 @@ contains foo_3 = a + 3 * b - c end function foo_3 end module mymod -! { dg-final { cleanup-modules "mymod" } } diff --git a/gcc/testsuite/gfortran.dg/dependency_19.f90 b/gcc/testsuite/gfortran.dg/dependency_19.f90 index b0af158553e2..3d20cc19697f 100644 --- a/gcc/testsuite/gfortran.dg/dependency_19.f90 +++ b/gcc/testsuite/gfortran.dg/dependency_19.f90 @@ -31,4 +31,3 @@ contains end subroutine construct end module gfcbug49 -! { dg-final { cleanup-modules "gfcbug49" } } diff --git a/gcc/testsuite/gfortran.dg/dependency_23.f90 b/gcc/testsuite/gfortran.dg/dependency_23.f90 index 447d626c5336..5a90cdaaa0cf 100644 --- a/gcc/testsuite/gfortran.dg/dependency_23.f90 +++ b/gcc/testsuite/gfortran.dg/dependency_23.f90 @@ -52,6 +52,3 @@ end module rg0045_stuff use rg0045_stuff call rg0045(1, 2, 3) end -! { dg-final { cleanup-modules "rg0045_stuff" } } - - diff --git a/gcc/testsuite/gfortran.dg/dependency_24.f90 b/gcc/testsuite/gfortran.dg/dependency_24.f90 index 9645f207538f..81c2be288acd 100644 --- a/gcc/testsuite/gfortran.dg/dependency_24.f90 +++ b/gcc/testsuite/gfortran.dg/dependency_24.f90 @@ -78,4 +78,3 @@ contains if (any (a%j .ne. 99)) call abort end subroutine end -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/dependency_25.f90 b/gcc/testsuite/gfortran.dg/dependency_25.f90 index 141811eea1c5..f2517f52ebf2 100644 --- a/gcc/testsuite/gfortran.dg/dependency_25.f90 +++ b/gcc/testsuite/gfortran.dg/dependency_25.f90 @@ -91,5 +91,3 @@ program TestProgram if (any (abs(Table%RealData(:,4) - 1) > epsilon(1.0))) call abort () if (any (abs(Table%RealData(:,[1,2,3,5]) - 42) > epsilon(1.0))) call abort () end program TestProgram - -! { dg-final { cleanup-modules "unitvalue_module" } } diff --git a/gcc/testsuite/gfortran.dg/dependency_26.f90 b/gcc/testsuite/gfortran.dg/dependency_26.f90 index e893d992c5de..d37307c5cc4a 100644 --- a/gcc/testsuite/gfortran.dg/dependency_26.f90 +++ b/gcc/testsuite/gfortran.dg/dependency_26.f90 @@ -47,7 +47,6 @@ END MODULE M1 cell%h = reshape ([(real(i), i = 1, 9)], [3, 3]) call s1 (cell) end -! { dg-final { cleanup-modules "m1 m2" } } ! { dg-final { scan-tree-dump-times "&a" 1 "original" } } ! { dg-final { scan-tree-dump-times "pack" 0 "original" } } ! { dg-final { cleanup-tree-dump "original" } } diff --git a/gcc/testsuite/gfortran.dg/dependency_28.f90 b/gcc/testsuite/gfortran.dg/dependency_28.f90 index 5d70abe395ec..bcb6e663adc2 100644 --- a/gcc/testsuite/gfortran.dg/dependency_28.f90 +++ b/gcc/testsuite/gfortran.dg/dependency_28.f90 @@ -18,4 +18,3 @@ contains a(c%k:c%m) = a(c%i:c%j) + b(c%k:c%m) ! { dg-warning "Creating array temporary" } end subroutine foo end module foobar -! { dg-final { cleanup-modules "foobar" } } diff --git a/gcc/testsuite/gfortran.dg/dependency_34.f90 b/gcc/testsuite/gfortran.dg/dependency_34.f90 index 82d286ebbcdf..db6ba01f9de8 100644 --- a/gcc/testsuite/gfortran.dg/dependency_34.f90 +++ b/gcc/testsuite/gfortran.dg/dependency_34.f90 @@ -19,4 +19,3 @@ program main a(bar(i,i+2):2) = a(bar(i,i+2):2) a(int(i,kind=2):5) = a(int(i,kind=2)+1:6) end program main -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/dependency_35.f90 b/gcc/testsuite/gfortran.dg/dependency_35.f90 index 11b9e8b94496..23b7e7460731 100644 --- a/gcc/testsuite/gfortran.dg/dependency_35.f90 +++ b/gcc/testsuite/gfortran.dg/dependency_35.f90 @@ -21,4 +21,3 @@ program main a = bar(3,4)*5 + b e = sum(b,1) + 3 end program main -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/dependency_36.f90 b/gcc/testsuite/gfortran.dg/dependency_36.f90 index 920df2fc2ee3..f3c0ef760f4b 100644 --- a/gcc/testsuite/gfortran.dg/dependency_36.f90 +++ b/gcc/testsuite/gfortran.dg/dependency_36.f90 @@ -26,5 +26,3 @@ CONTAINS x = matmul(a,b) ! { dg-warning "Creating array temporary" } END SUBROUTINE GeneticOptimize END MODULE m - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/dependency_37.f90 b/gcc/testsuite/gfortran.dg/dependency_37.f90 index a66f5aff3eac..12900c74f76f 100644 --- a/gcc/testsuite/gfortran.dg/dependency_37.f90 +++ b/gcc/testsuite/gfortran.dg/dependency_37.f90 @@ -46,4 +46,3 @@ program TestProgram Table%RealData = 1 Table%RealData(:,1) = Table%RealData(:,1) * CENTIMETER end program TestProgram -! { dg-final { cleanup-modules "unitvalue_module" } } diff --git a/gcc/testsuite/gfortran.dg/dependency_39.f90 b/gcc/testsuite/gfortran.dg/dependency_39.f90 index 68c48a4dc817..357827c7e7ff 100644 --- a/gcc/testsuite/gfortran.dg/dependency_39.f90 +++ b/gcc/testsuite/gfortran.dg/dependency_39.f90 @@ -34,4 +34,3 @@ program main deallocate(t%data) deallocate(t) end program main -! { dg-final { cleanup-modules "m1" } } diff --git a/gcc/testsuite/gfortran.dg/der_charlen_1.f90 b/gcc/testsuite/gfortran.dg/der_charlen_1.f90 index 4bdace228d97..9f394c73f25a 100644 --- a/gcc/testsuite/gfortran.dg/der_charlen_1.f90 +++ b/gcc/testsuite/gfortran.dg/der_charlen_1.f90 @@ -22,5 +22,3 @@ CONTAINS type(T), intent(in) :: X end subroutine end module another_core - -! { dg-final { cleanup-modules "core another_core" } } diff --git a/gcc/testsuite/gfortran.dg/der_io_2.f90 b/gcc/testsuite/gfortran.dg/der_io_2.f90 index 09878b690e91..e102a97a5755 100644 --- a/gcc/testsuite/gfortran.dg/der_io_2.f90 +++ b/gcc/testsuite/gfortran.dg/der_io_2.f90 @@ -51,5 +51,3 @@ program prog write (*, *) z ! { dg-error "PRIVATE components" } write (*, *) zb end program prog - -! { dg-final { cleanup-modules "gfortran2" } } diff --git a/gcc/testsuite/gfortran.dg/der_io_3.f90 b/gcc/testsuite/gfortran.dg/der_io_3.f90 index 1cb370ce17c7..13035fe98614 100644 --- a/gcc/testsuite/gfortran.dg/der_io_3.f90 +++ b/gcc/testsuite/gfortran.dg/der_io_3.f90 @@ -41,5 +41,3 @@ end module m2 use m2 call test end - -! { dg-final { cleanup-modules "m1 m2" } } diff --git a/gcc/testsuite/gfortran.dg/der_pointer_1.f90 b/gcc/testsuite/gfortran.dg/der_pointer_1.f90 index b9f98f518b9b..bf4ffc320f61 100644 --- a/gcc/testsuite/gfortran.dg/der_pointer_1.f90 +++ b/gcc/testsuite/gfortran.dg/der_pointer_1.f90 @@ -16,5 +16,3 @@ module test type(x_t), pointer :: x end module test - -! { dg-final { cleanup-modules "test" } } diff --git a/gcc/testsuite/gfortran.dg/der_pointer_3.f90 b/gcc/testsuite/gfortran.dg/der_pointer_3.f90 index ad9f7a7f880c..ed56ffc6c0cb 100644 --- a/gcc/testsuite/gfortran.dg/der_pointer_3.f90 +++ b/gcc/testsuite/gfortran.dg/der_pointer_3.f90 @@ -16,5 +16,3 @@ end module ints program size_test use ints end program size_test - -! { dg-final { cleanup-modules "ints" } } diff --git a/gcc/testsuite/gfortran.dg/der_pointer_4.f90 b/gcc/testsuite/gfortran.dg/der_pointer_4.f90 index 260afa4937e0..ec4814673691 100644 --- a/gcc/testsuite/gfortran.dg/der_pointer_4.f90 +++ b/gcc/testsuite/gfortran.dg/der_pointer_4.f90 @@ -9,5 +9,3 @@ module crash end type foo type (foo), save :: bar end module crash - -! { dg-final { cleanup-modules "crash" } } diff --git a/gcc/testsuite/gfortran.dg/derived_array_intrinisics_1.f90 b/gcc/testsuite/gfortran.dg/derived_array_intrinisics_1.f90 index 6056c83aaac3..274aada6aad3 100644 --- a/gcc/testsuite/gfortran.dg/derived_array_intrinisics_1.f90 +++ b/gcc/testsuite/gfortran.dg/derived_array_intrinisics_1.f90 @@ -29,4 +29,3 @@ end ! { dg-final { scan-tree-dump-times "j = 50" 1 "original" } } ! { dg-final { cleanup-tree-dump "original" } } -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/derived_comp_array_ref_1.f90 b/gcc/testsuite/gfortran.dg/derived_comp_array_ref_1.f90 index 1a868f3910e2..bbc109d92bda 100644 --- a/gcc/testsuite/gfortran.dg/derived_comp_array_ref_1.f90 +++ b/gcc/testsuite/gfortran.dg/derived_comp_array_ref_1.f90 @@ -31,5 +31,3 @@ end module gd_calc call activate_gd_calcs (used_, outputs_) if (any (outputs_(ndim:1:-1)%used .neqv. used_)) call abort () end - -! { dg-final { cleanup-modules "gd_calc" } } diff --git a/gcc/testsuite/gfortran.dg/derived_comp_array_ref_2.f90 b/gcc/testsuite/gfortran.dg/derived_comp_array_ref_2.f90 index 0530b0e6ea6b..014a3fb809b3 100644 --- a/gcc/testsuite/gfortran.dg/derived_comp_array_ref_2.f90 +++ b/gcc/testsuite/gfortran.dg/derived_comp_array_ref_2.f90 @@ -29,4 +29,3 @@ END MODULE cdf_beta_mod call cdf_beta (1, 99) call cdf_beta (2, 999) end -! { dg-final { cleanup-modules "cdf_aux_mod cdf_beta_mod" } } diff --git a/gcc/testsuite/gfortran.dg/derived_comp_array_ref_3.f90 b/gcc/testsuite/gfortran.dg/derived_comp_array_ref_3.f90 index 7a0b77ea802b..a3bb78d03744 100644 --- a/gcc/testsuite/gfortran.dg/derived_comp_array_ref_3.f90 +++ b/gcc/testsuite/gfortran.dg/derived_comp_array_ref_3.f90 @@ -26,4 +26,3 @@ END MODULE cdf_nc_chisq_mod use cdf_nc_chisq_mod call local_cum_nc_chisq end -! { dg-final { cleanup-modules "cdf_nc_chisq_mod" } } diff --git a/gcc/testsuite/gfortran.dg/derived_comp_array_ref_4.f90 b/gcc/testsuite/gfortran.dg/derived_comp_array_ref_4.f90 index 0c7853989e52..1fe03fc6510a 100644 --- a/gcc/testsuite/gfortran.dg/derived_comp_array_ref_4.f90 +++ b/gcc/testsuite/gfortran.dg/derived_comp_array_ref_4.f90 @@ -35,4 +35,3 @@ end module gfcbug70 call chk (2) call chk (1) end -! { dg-final { cleanup-modules "foo gfcbug70" } } diff --git a/gcc/testsuite/gfortran.dg/derived_comp_array_ref_6.f90 b/gcc/testsuite/gfortran.dg/derived_comp_array_ref_6.f90 index 36a30672e322..c0fb7c86cace 100644 --- a/gcc/testsuite/gfortran.dg/derived_comp_array_ref_6.f90 +++ b/gcc/testsuite/gfortran.dg/derived_comp_array_ref_6.f90 @@ -23,5 +23,3 @@ CALL set_bound(the_beta%parameters(1:which)) ! { dg-error "Rank mismatch" } END SUBROUTINE cdf_beta END MODULE cdf_beta_mod - -! { dg-final { cleanup-modules "cdf_aux_mod" } } diff --git a/gcc/testsuite/gfortran.dg/derived_constructor_comps_1.f90 b/gcc/testsuite/gfortran.dg/derived_constructor_comps_1.f90 index 83d127931c76..1c02a31c7a31 100644 --- a/gcc/testsuite/gfortran.dg/derived_constructor_comps_1.f90 +++ b/gcc/testsuite/gfortran.dg/derived_constructor_comps_1.f90 @@ -54,4 +54,3 @@ contains end function foo end program prog -! { dg-final { cleanup-modules "foo_mod" } } diff --git a/gcc/testsuite/gfortran.dg/derived_constructor_comps_3.f90 b/gcc/testsuite/gfortran.dg/derived_constructor_comps_3.f90 index 0aa2e4e1c185..9ce03beb797e 100644 --- a/gcc/testsuite/gfortran.dg/derived_constructor_comps_3.f90 +++ b/gcc/testsuite/gfortran.dg/derived_constructor_comps_3.f90 @@ -19,4 +19,3 @@ program bug4_structure t = bug4() write(*,*) t end program bug4_structure -! { dg-final { cleanup-modules "bug4_mod" } } diff --git a/gcc/testsuite/gfortran.dg/derived_function_interface_1.f90 b/gcc/testsuite/gfortran.dg/derived_function_interface_1.f90 index b7ee4df89a70..24a009509128 100644 --- a/gcc/testsuite/gfortran.dg/derived_function_interface_1.f90 +++ b/gcc/testsuite/gfortran.dg/derived_function_interface_1.f90 @@ -42,4 +42,3 @@ contains end function fun ! { dg-error "Expecting END PROGRAM" } end -! { dg-final { cleanup-modules "kinds" } } diff --git a/gcc/testsuite/gfortran.dg/derived_init_2.f90 b/gcc/testsuite/gfortran.dg/derived_init_2.f90 index 18d7544ecd88..10a16b532a26 100644 --- a/gcc/testsuite/gfortran.dg/derived_init_2.f90 +++ b/gcc/testsuite/gfortran.dg/derived_init_2.f90 @@ -45,4 +45,3 @@ program main call foo(aa) end program main -! { dg-final { cleanup-modules "dt subs" } } diff --git a/gcc/testsuite/gfortran.dg/derived_pointer_recursion.f90 b/gcc/testsuite/gfortran.dg/derived_pointer_recursion.f90 index 4af2ceefecba..4f4b70a4cc9e 100644 --- a/gcc/testsuite/gfortran.dg/derived_pointer_recursion.f90 +++ b/gcc/testsuite/gfortran.dg/derived_pointer_recursion.f90 @@ -19,5 +19,3 @@ end module llo ! copyright 1996 Loren P. Meissner -- May be distributed if this line is included. ! Linked List operations with Pointer to Pointer - -! { dg-final { cleanup-modules "llo" } } diff --git a/gcc/testsuite/gfortran.dg/derived_pointer_recursion_2.f90 b/gcc/testsuite/gfortran.dg/derived_pointer_recursion_2.f90 index f6bda4d0531f..675be1b3c097 100644 --- a/gcc/testsuite/gfortran.dg/derived_pointer_recursion_2.f90 +++ b/gcc/testsuite/gfortran.dg/derived_pointer_recursion_2.f90 @@ -43,6 +43,3 @@ program pr40594 if (ap%initialized .neqv. .false.) call abort() END - -! { dg-final { cleanup-modules "atom_types" } } - diff --git a/gcc/testsuite/gfortran.dg/derived_recursion.f90 b/gcc/testsuite/gfortran.dg/derived_recursion.f90 index d0c0ea8d467c..d52732ff2798 100644 --- a/gcc/testsuite/gfortran.dg/derived_recursion.f90 +++ b/gcc/testsuite/gfortran.dg/derived_recursion.f90 @@ -22,5 +22,3 @@ end module snafu ! use snafu ! foo%v = 1 ! end - -! { dg-final { cleanup-modules "snafu" } } diff --git a/gcc/testsuite/gfortran.dg/derived_sub.f90 b/gcc/testsuite/gfortran.dg/derived_sub.f90 index 9b6624579c2d..1750ada124a0 100644 --- a/gcc/testsuite/gfortran.dg/derived_sub.f90 +++ b/gcc/testsuite/gfortran.dg/derived_sub.f90 @@ -31,4 +31,3 @@ contains end subroutine end module -! { dg-final { cleanup-modules "modone modtwo" } } diff --git a/gcc/testsuite/gfortran.dg/dummy_functions_1.f90 b/gcc/testsuite/gfortran.dg/dummy_functions_1.f90 index 8076cf911a9f..dfcf644c2556 100644 --- a/gcc/testsuite/gfortran.dg/dummy_functions_1.f90 +++ b/gcc/testsuite/gfortran.dg/dummy_functions_1.f90 @@ -34,5 +34,3 @@ program test use innerfun call foo(3,f) end program test - -! { dg-final { cleanup-modules "innerfun outerfun" } } diff --git a/gcc/testsuite/gfortran.dg/dummy_procedure_1.f90 b/gcc/testsuite/gfortran.dg/dummy_procedure_1.f90 index 55107b69a629..564aff23fc70 100644 --- a/gcc/testsuite/gfortran.dg/dummy_procedure_1.f90 +++ b/gcc/testsuite/gfortran.dg/dummy_procedure_1.f90 @@ -48,5 +48,3 @@ contains w = 1 end function w end - -! { dg-final { cleanup-modules "m1" } } diff --git a/gcc/testsuite/gfortran.dg/dummy_procedure_2.f90 b/gcc/testsuite/gfortran.dg/dummy_procedure_2.f90 index b58980863942..dd609bd0009d 100644 --- a/gcc/testsuite/gfortran.dg/dummy_procedure_2.f90 +++ b/gcc/testsuite/gfortran.dg/dummy_procedure_2.f90 @@ -31,4 +31,3 @@ contains print *,integrate (g,0d0,3d0) end subroutine foo2 end -! { dg-final { cleanup-modules "integrator" } } diff --git a/gcc/testsuite/gfortran.dg/dummy_procedure_3.f90 b/gcc/testsuite/gfortran.dg/dummy_procedure_3.f90 index cde2f0166af1..2a17b06d19fa 100644 --- a/gcc/testsuite/gfortran.dg/dummy_procedure_3.f90 +++ b/gcc/testsuite/gfortran.dg/dummy_procedure_3.f90 @@ -36,5 +36,3 @@ contains end do end function end -! { dg-final { cleanup-modules "m" } } - diff --git a/gcc/testsuite/gfortran.dg/dummy_procedure_4.f90 b/gcc/testsuite/gfortran.dg/dummy_procedure_4.f90 index 498685bde38c..8c1e55417e00 100644 --- a/gcc/testsuite/gfortran.dg/dummy_procedure_4.f90 +++ b/gcc/testsuite/gfortran.dg/dummy_procedure_4.f90 @@ -44,5 +44,3 @@ contains end subroutine end - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/dummy_procedure_6.f90 b/gcc/testsuite/gfortran.dg/dummy_procedure_6.f90 index fa9ebfe3546b..dfd51d65a74a 100644 --- a/gcc/testsuite/gfortran.dg/dummy_procedure_6.f90 +++ b/gcc/testsuite/gfortran.dg/dummy_procedure_6.f90 @@ -67,5 +67,3 @@ contains end subroutine end program - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/dummy_procedure_7.f90 b/gcc/testsuite/gfortran.dg/dummy_procedure_7.f90 index 32cd65ae8b66..0e5b7d9eef14 100644 --- a/gcc/testsuite/gfortran.dg/dummy_procedure_7.f90 +++ b/gcc/testsuite/gfortran.dg/dummy_procedure_7.f90 @@ -61,5 +61,3 @@ program test call sol(cost) if (icheck /= 1) call abort () end program test - -! { dg-final { cleanup-modules "t tt check" } } diff --git a/gcc/testsuite/gfortran.dg/dynamic_dispatch_1.f03 b/gcc/testsuite/gfortran.dg/dynamic_dispatch_1.f03 index 2182dce3e4f7..c07b189e2175 100644 --- a/gcc/testsuite/gfortran.dg/dynamic_dispatch_1.f03 +++ b/gcc/testsuite/gfortran.dg/dynamic_dispatch_1.f03 @@ -76,4 +76,3 @@ end module m if (a%prod() .ne. 42) call abort if (a%extract (4) .ne. 168) call abort end -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/dynamic_dispatch_10.f03 b/gcc/testsuite/gfortran.dg/dynamic_dispatch_10.f03 index 21cf1409e1b0..2831b088743e 100644 --- a/gcc/testsuite/gfortran.dg/dynamic_dispatch_10.f03 +++ b/gcc/testsuite/gfortran.dg/dynamic_dispatch_10.f03 @@ -167,5 +167,3 @@ program main end do end - -! { dg-final { cleanup-modules "basestrategy laxwendroffstrategy kestrategy" } } diff --git a/gcc/testsuite/gfortran.dg/dynamic_dispatch_11.f03 b/gcc/testsuite/gfortran.dg/dynamic_dispatch_11.f03 index e4abcb2846eb..a4fb39a80903 100644 --- a/gcc/testsuite/gfortran.dg/dynamic_dispatch_11.f03 +++ b/gcc/testsuite/gfortran.dg/dynamic_dispatch_11.f03 @@ -30,6 +30,3 @@ end module allocate(a) if (a%get()/=1) call abort() end - - -! { dg-final { cleanup-modules "mod1 mod2" } } diff --git a/gcc/testsuite/gfortran.dg/dynamic_dispatch_2.f03 b/gcc/testsuite/gfortran.dg/dynamic_dispatch_2.f03 index 95ce8372325c..c30ce6a808e1 100644 --- a/gcc/testsuite/gfortran.dg/dynamic_dispatch_2.f03 +++ b/gcc/testsuite/gfortran.dg/dynamic_dispatch_2.f03 @@ -94,4 +94,3 @@ end module m call a%extract (4, i) if (i .ne. 168) call abort end -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/dynamic_dispatch_3.f03 b/gcc/testsuite/gfortran.dg/dynamic_dispatch_3.f03 index 884d3426039d..41c784d17050 100644 --- a/gcc/testsuite/gfortran.dg/dynamic_dispatch_3.f03 +++ b/gcc/testsuite/gfortran.dg/dynamic_dispatch_3.f03 @@ -83,4 +83,3 @@ end module m2 if (a%prod() .ne. 42) call abort if (a%extract (4) .ne. 168) call abort end -! { dg-final { cleanup-modules "m1, m2" } } diff --git a/gcc/testsuite/gfortran.dg/dynamic_dispatch_4.f03 b/gcc/testsuite/gfortran.dg/dynamic_dispatch_4.f03 index b72819acc4ce..b31f910cfb0f 100644 --- a/gcc/testsuite/gfortran.dg/dynamic_dispatch_4.f03 +++ b/gcc/testsuite/gfortran.dg/dynamic_dispatch_4.f03 @@ -92,5 +92,3 @@ end module a_bar_mod call a%doit if (a%getit () .ne. 3) call abort end -! { dg-final { cleanup-modules "foo_mod s_bar_mod a_bar_mod" } } - diff --git a/gcc/testsuite/gfortran.dg/dynamic_dispatch_5.f03 b/gcc/testsuite/gfortran.dg/dynamic_dispatch_5.f03 index 9cc16bc1c097..dee6aae596d1 100644 --- a/gcc/testsuite/gfortran.dg/dynamic_dispatch_5.f03 +++ b/gcc/testsuite/gfortran.dg/dynamic_dispatch_5.f03 @@ -183,5 +183,3 @@ end module s_mat_mod call a%scal (1.0_spk_, info) if (info .ne. 700) call abort end -! { dg-final { cleanup-modules "const_mod base_mat_mod s_base_mat_mod s_mat_mod" } } - diff --git a/gcc/testsuite/gfortran.dg/dynamic_dispatch_6.f03 b/gcc/testsuite/gfortran.dg/dynamic_dispatch_6.f03 index e2d880e0efa0..e54966bf1e17 100644 --- a/gcc/testsuite/gfortran.dg/dynamic_dispatch_6.f03 +++ b/gcc/testsuite/gfortran.dg/dynamic_dispatch_6.f03 @@ -65,5 +65,3 @@ program main allocate (periodic_5th_factory :: field_creator) u => field_creator%create() end program - -! { dg-final { cleanup-modules "field_module periodic_5th_order_module field_factory_module periodic_5th_factory_module" } } diff --git a/gcc/testsuite/gfortran.dg/dynamic_dispatch_7.f03 b/gcc/testsuite/gfortran.dg/dynamic_dispatch_7.f03 index 3cd051047287..89ed05c753a3 100644 --- a/gcc/testsuite/gfortran.dg/dynamic_dispatch_7.f03 +++ b/gcc/testsuite/gfortran.dg/dynamic_dispatch_7.f03 @@ -56,6 +56,4 @@ end module z%a => y if ((z%sizeof() .ne. 2) .or. (z%a%sizeof() .ne. 2)) call abort end - -! { dg-final { cleanup-modules "m1 m2 m3" } } diff --git a/gcc/testsuite/gfortran.dg/dynamic_dispatch_8.f03 b/gcc/testsuite/gfortran.dg/dynamic_dispatch_8.f03 index 4f3d8069b433..889cd33c033a 100644 --- a/gcc/testsuite/gfortran.dg/dynamic_dispatch_8.f03 +++ b/gcc/testsuite/gfortran.dg/dynamic_dispatch_8.f03 @@ -103,6 +103,3 @@ program testd10 if (a%getit() .ne. 3) call abort end program testd10 - -! { dg-final { cleanup-modules "foo_mod foo2_mod bar_mod" } } - diff --git a/gcc/testsuite/gfortran.dg/dynamic_dispatch_9.f03 b/gcc/testsuite/gfortran.dg/dynamic_dispatch_9.f03 index bf6a3d558702..9541fa8d698e 100644 --- a/gcc/testsuite/gfortran.dg/dynamic_dispatch_9.f03 +++ b/gcc/testsuite/gfortran.dg/dynamic_dispatch_9.f03 @@ -49,6 +49,3 @@ end if (o2%gen(3) .ne. 9) call abort end - -! { dg-final { cleanup-modules "m" } } - diff --git a/gcc/testsuite/gfortran.dg/elemental_args_check_2.f90 b/gcc/testsuite/gfortran.dg/elemental_args_check_2.f90 index e8b429305e83..51e69a49ee46 100644 --- a/gcc/testsuite/gfortran.dg/elemental_args_check_2.f90 +++ b/gcc/testsuite/gfortran.dg/elemental_args_check_2.f90 @@ -17,4 +17,3 @@ CONTAINS END INTERFACE END SUBROUTINE S1 END MODULE M1 -! { dg-final { cleanup-modules "m1" } } diff --git a/gcc/testsuite/gfortran.dg/elemental_dependency_2.f90 b/gcc/testsuite/gfortran.dg/elemental_dependency_2.f90 index 2282e8821f75..348c6c7aa502 100644 --- a/gcc/testsuite/gfortran.dg/elemental_dependency_2.f90 +++ b/gcc/testsuite/gfortran.dg/elemental_dependency_2.f90 @@ -32,5 +32,3 @@ contains call add (c , b ) end subroutine foo end module gfcbug82 - -! { dg-final { cleanup-modules "gfcbug82" } } diff --git a/gcc/testsuite/gfortran.dg/elemental_initializer_1.f90 b/gcc/testsuite/gfortran.dg/elemental_initializer_1.f90 index 0e717c947d21..7280e2582b08 100644 --- a/gcc/testsuite/gfortran.dg/elemental_initializer_1.f90 +++ b/gcc/testsuite/gfortran.dg/elemental_initializer_1.f90 @@ -31,5 +31,3 @@ contains end function len_ end module iso_varying_string - -! { dg-final { cleanup-modules "iso_varying_string" } } diff --git a/gcc/testsuite/gfortran.dg/elemental_non_intrinsic_dummy_1.f90 b/gcc/testsuite/gfortran.dg/elemental_non_intrinsic_dummy_1.f90 index b9404a0c0db4..c14a5d87fa5e 100644 --- a/gcc/testsuite/gfortran.dg/elemental_non_intrinsic_dummy_1.f90 +++ b/gcc/testsuite/gfortran.dg/elemental_non_intrinsic_dummy_1.f90 @@ -19,5 +19,3 @@ INTEGER FUNCTION SUB(XX) INTEGER :: XX SUB=XX() END - -! { dg-final { cleanup-modules "tt" } } diff --git a/gcc/testsuite/gfortran.dg/elemental_pointer_1.f90 b/gcc/testsuite/gfortran.dg/elemental_pointer_1.f90 index bce34527a86d..b5d99611c78f 100644 --- a/gcc/testsuite/gfortran.dg/elemental_pointer_1.f90 +++ b/gcc/testsuite/gfortran.dg/elemental_pointer_1.f90 @@ -9,5 +9,3 @@ CONTAINS POINTER :: LL ! { dg-error " POINTER attribute conflicts with ELEMENTAL attribute" } END FUNCTION LL END MODULE Test - -! { dg-final { cleanup-modules "test" } } diff --git a/gcc/testsuite/gfortran.dg/elemental_result_1.f90 b/gcc/testsuite/gfortran.dg/elemental_result_1.f90 index 09f785af765f..566303953ca0 100644 --- a/gcc/testsuite/gfortran.dg/elemental_result_1.f90 +++ b/gcc/testsuite/gfortran.dg/elemental_result_1.f90 @@ -18,4 +18,3 @@ CONTAINS INTEGER, pointer :: MM ! { dg-error "conflicts with ELEMENTAL" } END FUNCTION MM END MODULE Test -! { dg-final { cleanup-modules "test" } } diff --git a/gcc/testsuite/gfortran.dg/elemental_scalar_args_1.f90 b/gcc/testsuite/gfortran.dg/elemental_scalar_args_1.f90 index d180bc931d29..4e2a21ea82cc 100644 --- a/gcc/testsuite/gfortran.dg/elemental_scalar_args_1.f90 +++ b/gcc/testsuite/gfortran.dg/elemental_scalar_args_1.f90 @@ -84,4 +84,3 @@ contains if (any (b .ne. real_one)) call abort end subroutine test_real end program main -! { dg-final { cleanup-modules "polar_mod" } } diff --git a/gcc/testsuite/gfortran.dg/elemental_subroutine_1.f90 b/gcc/testsuite/gfortran.dg/elemental_subroutine_1.f90 index 802d1ed20ff5..a19a7807c16b 100644 --- a/gcc/testsuite/gfortran.dg/elemental_subroutine_1.f90 +++ b/gcc/testsuite/gfortran.dg/elemental_subroutine_1.f90 @@ -58,5 +58,3 @@ contains b = -a end subroutine foobar end - -! { dg-final { cleanup-modules "pr22146" } } diff --git a/gcc/testsuite/gfortran.dg/elemental_subroutine_2.f90 b/gcc/testsuite/gfortran.dg/elemental_subroutine_2.f90 index e95831186936..b7d9afe9e085 100644 --- a/gcc/testsuite/gfortran.dg/elemental_subroutine_2.f90 +++ b/gcc/testsuite/gfortran.dg/elemental_subroutine_2.f90 @@ -62,5 +62,3 @@ program test_assign if (any(reshape (i, (/4/)).ne.(/1,8,27,64/))) call abort () end program test_assign - -! { dg-final { cleanup-modules "type assign" } } diff --git a/gcc/testsuite/gfortran.dg/elemental_subroutine_3.f90 b/gcc/testsuite/gfortran.dg/elemental_subroutine_3.f90 index 1f93cd4a2c76..22c0b20b151a 100644 --- a/gcc/testsuite/gfortran.dg/elemental_subroutine_3.f90 +++ b/gcc/testsuite/gfortran.dg/elemental_subroutine_3.f90 @@ -48,6 +48,3 @@ program test y = reshape (z, (/6/)) if (any(y%x .ne. (/ 64000, 128000, 19200, 64, 128000, 256000/))) call abort () end program test - -! { dg-final { cleanup-modules "elem_assign" } } - diff --git a/gcc/testsuite/gfortran.dg/elemental_subroutine_4.f90 b/gcc/testsuite/gfortran.dg/elemental_subroutine_4.f90 index 9d2bc492f5c3..625810479c50 100644 --- a/gcc/testsuite/gfortran.dg/elemental_subroutine_4.f90 +++ b/gcc/testsuite/gfortran.dg/elemental_subroutine_4.f90 @@ -34,5 +34,3 @@ CONTAINS INTEGER, INTENT(IN) :: I,J END SUBROUTINE S END - -! { dg-final { cleanup-modules "elem_assign" } } diff --git a/gcc/testsuite/gfortran.dg/elemental_subroutine_6.f90 b/gcc/testsuite/gfortran.dg/elemental_subroutine_6.f90 index 44577c888b79..d26833710a7e 100644 --- a/gcc/testsuite/gfortran.dg/elemental_subroutine_6.f90 +++ b/gcc/testsuite/gfortran.dg/elemental_subroutine_6.f90 @@ -22,4 +22,3 @@ CONTAINS out(1, 1:42) = in(1, 1:42) END SUBROUTINE END MODULE foo -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/empty_derived_type.f90 b/gcc/testsuite/gfortran.dg/empty_derived_type.f90 index d6fad1235f36..6bf616c2c6ab 100644 --- a/gcc/testsuite/gfortran.dg/empty_derived_type.f90 +++ b/gcc/testsuite/gfortran.dg/empty_derived_type.f90 @@ -5,5 +5,3 @@ module stuff ! Empty! end type junk end module stuff - -! { dg-final { cleanup-modules "stuff" } } diff --git a/gcc/testsuite/gfortran.dg/entry_1.f90 b/gcc/testsuite/gfortran.dg/entry_1.f90 index c9048a0442ab..dae868ec8511 100644 --- a/gcc/testsuite/gfortran.dg/entry_1.f90 +++ b/gcc/testsuite/gfortran.dg/entry_1.f90 @@ -43,5 +43,3 @@ program p call test1 () call test2 () end program - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/entry_10.f90 b/gcc/testsuite/gfortran.dg/entry_10.f90 index 154d44ea9ba9..dc80c7949e04 100644 --- a/gcc/testsuite/gfortran.dg/entry_10.f90 +++ b/gcc/testsuite/gfortran.dg/entry_10.f90 @@ -33,4 +33,3 @@ end module if (e (1.0) .ne. 3.0) call abort () if (f (1 ) .ne. 4.0) call abort () end -! { dg-final { cleanup-modules "a" } } diff --git a/gcc/testsuite/gfortran.dg/entry_12.f90 b/gcc/testsuite/gfortran.dg/entry_12.f90 index 5513697a17cd..15e874e2b056 100644 --- a/gcc/testsuite/gfortran.dg/entry_12.f90 +++ b/gcc/testsuite/gfortran.dg/entry_12.f90 @@ -28,4 +28,3 @@ END MODULE ksbin1_aux_mod if (any ((/foo (), bar (99), foobar (), foobar (99), j (), k (99)/) .ne. & (/1, 2, 1, 2, 1, 2/))) Call abort () end -! { dg-final { cleanup-modules "ksbin1_aux_mod" } } diff --git a/gcc/testsuite/gfortran.dg/entry_13.f90 b/gcc/testsuite/gfortran.dg/entry_13.f90 index 3a45fc5ea02a..1858cc377358 100644 --- a/gcc/testsuite/gfortran.dg/entry_13.f90 +++ b/gcc/testsuite/gfortran.dg/entry_13.f90 @@ -76,5 +76,3 @@ program test z1 = y1==x1 if (abs(z1%x - 19.0_4/7.0_4) > epsilon(x1%x)) call abort () end program test -! { dg-final { cleanup-modules "type_mod" } } - diff --git a/gcc/testsuite/gfortran.dg/entry_14.f90 b/gcc/testsuite/gfortran.dg/entry_14.f90 index e0aa00078c4f..dfed19549f7a 100644 --- a/gcc/testsuite/gfortran.dg/entry_14.f90 +++ b/gcc/testsuite/gfortran.dg/entry_14.f90 @@ -99,5 +99,3 @@ contains if(abs(ent(27) + 216.0) > tiny(1.0)) call abort() end subroutine test4 end program main - -! { dg-final { cleanup-modules "m1 m2 m3 m4" } } diff --git a/gcc/testsuite/gfortran.dg/entry_16.f90 b/gcc/testsuite/gfortran.dg/entry_16.f90 index 384d99fd72c3..ba8eff86b8d7 100644 --- a/gcc/testsuite/gfortran.dg/entry_16.f90 +++ b/gcc/testsuite/gfortran.dg/entry_16.f90 @@ -41,4 +41,3 @@ END MODULE complex if (.not.((a + b) .eq. (b + a))) call abort () if (.not.((a + b) .eq. cx (4, 2))) call abort () end -! { dg-final { cleanup-modules "complex" } } diff --git a/gcc/testsuite/gfortran.dg/entry_18.f90 b/gcc/testsuite/gfortran.dg/entry_18.f90 index 0cfe842137e1..b9cc41740a62 100644 --- a/gcc/testsuite/gfortran.dg/entry_18.f90 +++ b/gcc/testsuite/gfortran.dg/entry_18.f90 @@ -33,4 +33,3 @@ entry glocalb( x, y ) y = x end subroutine end module -! { dg-final { cleanup-modules "gsub" } } diff --git a/gcc/testsuite/gfortran.dg/entry_3.f90 b/gcc/testsuite/gfortran.dg/entry_3.f90 index b4473df31bac..36595ee31e10 100644 --- a/gcc/testsuite/gfortran.dg/entry_3.f90 +++ b/gcc/testsuite/gfortran.dg/entry_3.f90 @@ -23,5 +23,3 @@ program entry_4_prog call bar(a) if (any (a .ne. (/3, 4/))) call abort end program - -! { dg-final { cleanup-modules "entry_4" } } diff --git a/gcc/testsuite/gfortran.dg/entry_6.f90 b/gcc/testsuite/gfortran.dg/entry_6.f90 index 103392606b99..c1d6c7cbb2db 100644 --- a/gcc/testsuite/gfortran.dg/entry_6.f90 +++ b/gcc/testsuite/gfortran.dg/entry_6.f90 @@ -52,5 +52,3 @@ end module foo if (z1((3,4)) .ne. (-5, 10)) call abort () if (z2((5,6)) .ne. (-9, 38)) call abort () end - -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/entry_7.f90 b/gcc/testsuite/gfortran.dg/entry_7.f90 index 6dd87f437f8d..0ffcf34ebe73 100644 --- a/gcc/testsuite/gfortran.dg/entry_7.f90 +++ b/gcc/testsuite/gfortran.dg/entry_7.f90 @@ -22,6 +22,3 @@ CONTAINS bar = "abcd" end function END MODULE TT - - -! { dg-final { cleanup-modules "tt" } } diff --git a/gcc/testsuite/gfortran.dg/entry_9.f90 b/gcc/testsuite/gfortran.dg/entry_9.f90 index 5dcb6e3b173c..ecffcd83a601 100644 --- a/gcc/testsuite/gfortran.dg/entry_9.f90 +++ b/gcc/testsuite/gfortran.dg/entry_9.f90 @@ -27,5 +27,3 @@ program main if (F2(4) /= -4) call abort() if (F1(1) /= -1) call abort() end program main - -! { dg-final { cleanup-modules "m1" } } diff --git a/gcc/testsuite/gfortran.dg/entry_dummy_ref_2.f90 b/gcc/testsuite/gfortran.dg/entry_dummy_ref_2.f90 index 20f1c1065469..1634e25d4b71 100644 --- a/gcc/testsuite/gfortran.dg/entry_dummy_ref_2.f90 +++ b/gcc/testsuite/gfortran.dg/entry_dummy_ref_2.f90 @@ -16,5 +16,3 @@ FUNCTION F1(I) RESULT(RF1) END FUNCTION F1 END MODULE M1 END - -! { dg-final { cleanup-modules "m1" } } diff --git a/gcc/testsuite/gfortran.dg/enum_10.f90 b/gcc/testsuite/gfortran.dg/enum_10.f90 index 99a16901c4b5..b387fe339e92 100644 --- a/gcc/testsuite/gfortran.dg/enum_10.f90 +++ b/gcc/testsuite/gfortran.dg/enum_10.f90 @@ -60,5 +60,3 @@ call f4 (one4, 1) call f4 (two4, 2) call f4 (max4, huge(1_4)+0) end - -! { dg-final { cleanup-modules "enum_10" } } diff --git a/gcc/testsuite/gfortran.dg/equiv_constraint_3.f90 b/gcc/testsuite/gfortran.dg/equiv_constraint_3.f90 index c39d1448aa81..99e9248b39b6 100644 --- a/gcc/testsuite/gfortran.dg/equiv_constraint_3.f90 +++ b/gcc/testsuite/gfortran.dg/equiv_constraint_3.f90 @@ -9,5 +9,3 @@ USE TEST, ONLY : K=>I INTEGER :: L EQUIVALENCE(K,L) ! { dg-error "conflicts with USE ASSOCIATED attribute" } END - -! { dg-final { cleanup-modules "test" } } diff --git a/gcc/testsuite/gfortran.dg/equiv_constraint_7.f90 b/gcc/testsuite/gfortran.dg/equiv_constraint_7.f90 index 080cdef54833..872e05b90fca 100644 --- a/gcc/testsuite/gfortran.dg/equiv_constraint_7.f90 +++ b/gcc/testsuite/gfortran.dg/equiv_constraint_7.f90 @@ -9,4 +9,3 @@ EQUIVALENCE(I,J) END MODULE DATA END -! { dg-final { cleanup-modules "data" } } diff --git a/gcc/testsuite/gfortran.dg/error_recovery_3.f90 b/gcc/testsuite/gfortran.dg/error_recovery_3.f90 index 35804be89441..52699037e50d 100644 --- a/gcc/testsuite/gfortran.dg/error_recovery_3.f90 +++ b/gcc/testsuite/gfortran.dg/error_recovery_3.f90 @@ -7,5 +7,3 @@ MODULE M1 END MODULE M1 USE M1, ONLY: I,&! { dg-error "Missing" } -! { dg-final { cleanup-modules "m1" } } - diff --git a/gcc/testsuite/gfortran.dg/extends_1.f03 b/gcc/testsuite/gfortran.dg/extends_1.f03 index 57a50732c559..bb01728a5e76 100644 --- a/gcc/testsuite/gfortran.dg/extends_1.f03 +++ b/gcc/testsuite/gfortran.dg/extends_1.f03 @@ -69,5 +69,3 @@ contains new_person%supervisor => supervisor end function end - -! { dg-final { cleanup-modules "persons person_education" } } diff --git a/gcc/testsuite/gfortran.dg/extends_10.f03 b/gcc/testsuite/gfortran.dg/extends_10.f03 index fbcaa7efc3f6..40e928e3e542 100644 --- a/gcc/testsuite/gfortran.dg/extends_10.f03 +++ b/gcc/testsuite/gfortran.dg/extends_10.f03 @@ -30,5 +30,3 @@ program pr print *,a%t1%i print *,b%u1%j ! { dg-error "is a PRIVATE component of" } end program - -! { dg-final { cleanup-modules "mo" } } diff --git a/gcc/testsuite/gfortran.dg/extends_12.f03 b/gcc/testsuite/gfortran.dg/extends_12.f03 index a93f6d0f1220..972ab3a74357 100644 --- a/gcc/testsuite/gfortran.dg/extends_12.f03 +++ b/gcc/testsuite/gfortran.dg/extends_12.f03 @@ -20,5 +20,3 @@ program diff_01 implicit none call create_ext() end program - -! { dg-final { cleanup-modules "mod_diff_01" } } diff --git a/gcc/testsuite/gfortran.dg/extends_13.f03 b/gcc/testsuite/gfortran.dg/extends_13.f03 index 5d986877df27..9181004997a7 100644 --- a/gcc/testsuite/gfortran.dg/extends_13.f03 +++ b/gcc/testsuite/gfortran.dg/extends_13.f03 @@ -26,5 +26,3 @@ end module use type_definitions use elliptical_elements end - -! { dg-final { cleanup-modules "type_definitions elliptical_elements" } } diff --git a/gcc/testsuite/gfortran.dg/extends_2.f03 b/gcc/testsuite/gfortran.dg/extends_2.f03 index aabbf662a4ff..ca92378a72fc 100644 --- a/gcc/testsuite/gfortran.dg/extends_2.f03 +++ b/gcc/testsuite/gfortran.dg/extends_2.f03 @@ -62,5 +62,3 @@ contains supervisor) end function end - -! { dg-final { cleanup-modules "persons person_education" } } diff --git a/gcc/testsuite/gfortran.dg/extends_3.f03 b/gcc/testsuite/gfortran.dg/extends_3.f03 index 27ae670d95ff..eabac67b6849 100644 --- a/gcc/testsuite/gfortran.dg/extends_3.f03 +++ b/gcc/testsuite/gfortran.dg/extends_3.f03 @@ -67,5 +67,3 @@ contains SUPERVISOR = supervisor) end function end - -! { dg-final { cleanup-modules "persons person_education" } } diff --git a/gcc/testsuite/gfortran.dg/extends_4.f03 b/gcc/testsuite/gfortran.dg/extends_4.f03 index 831c9ebb6e47..a0c91fd1984e 100644 --- a/gcc/testsuite/gfortran.dg/extends_4.f03 +++ b/gcc/testsuite/gfortran.dg/extends_4.f03 @@ -48,5 +48,3 @@ end module mymod q = d (b = set_b (), id = 99) call check_b (q%b) end - -! { dg-final { cleanup-modules "mymod" } } diff --git a/gcc/testsuite/gfortran.dg/extends_5.f03 b/gcc/testsuite/gfortran.dg/extends_5.f03 index 5146d456355b..d2b011764b2f 100644 --- a/gcc/testsuite/gfortran.dg/extends_5.f03 +++ b/gcc/testsuite/gfortran.dg/extends_5.f03 @@ -23,5 +23,3 @@ end module m type, extends(dt) :: dt_type ! { dg-error "because it is BIND" } end type ! { dg-error "Expecting END PROGRAM" } end - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/extends_6.f03 b/gcc/testsuite/gfortran.dg/extends_6.f03 index a50a9b751b1f..fd2b9e7029d4 100644 --- a/gcc/testsuite/gfortran.dg/extends_6.f03 +++ b/gcc/testsuite/gfortran.dg/extends_6.f03 @@ -45,5 +45,3 @@ contains foo_dt%dt%day = 1 ! { dg-error "not a member" } end subroutine end - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/extends_7.f03 b/gcc/testsuite/gfortran.dg/extends_7.f03 index ebb2fcc3efb7..35f74d001b68 100644 --- a/gcc/testsuite/gfortran.dg/extends_7.f03 +++ b/gcc/testsuite/gfortran.dg/extends_7.f03 @@ -21,5 +21,3 @@ MODULE m2 END TYPE subt END MODULE m2 - -! { dg-final { cleanup-modules "m1 m2" } } diff --git a/gcc/testsuite/gfortran.dg/extends_8.f03 b/gcc/testsuite/gfortran.dg/extends_8.f03 index 4af5ab9327c3..0773f329a02f 100644 --- a/gcc/testsuite/gfortran.dg/extends_8.f03 +++ b/gcc/testsuite/gfortran.dg/extends_8.f03 @@ -14,4 +14,3 @@ end module use m, only: A end -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/extends_9.f03 b/gcc/testsuite/gfortran.dg/extends_9.f03 index f59b97396b3e..a8d2d1b66a06 100644 --- a/gcc/testsuite/gfortran.dg/extends_9.f03 +++ b/gcc/testsuite/gfortran.dg/extends_9.f03 @@ -33,4 +33,3 @@ END MODULE END -! { dg-final { cleanup-modules "run_example_fortran03" } } diff --git a/gcc/testsuite/gfortran.dg/external_procedures_2.f90 b/gcc/testsuite/gfortran.dg/external_procedures_2.f90 index 3f13dac3da0c..6566e653e478 100644 --- a/gcc/testsuite/gfortran.dg/external_procedures_2.f90 +++ b/gcc/testsuite/gfortran.dg/external_procedures_2.f90 @@ -38,4 +38,3 @@ program gfcbug53 call foo (x0) print *, x0 end program gfcbug53 -! { dg-final { cleanup-modules "mod1 mod2" } } diff --git a/gcc/testsuite/gfortran.dg/finalize_1.f08 b/gcc/testsuite/gfortran.dg/finalize_1.f08 index e1501ef66b82..391a0f13efad 100644 --- a/gcc/testsuite/gfortran.dg/finalize_1.f08 +++ b/gcc/testsuite/gfortran.dg/finalize_1.f08 @@ -27,5 +27,3 @@ PROGRAM finalizer IMPLICIT NONE ! Do nothing here END PROGRAM finalizer - -! { dg-final { cleanup-modules "final_type" } } diff --git a/gcc/testsuite/gfortran.dg/finalize_2.f03 b/gcc/testsuite/gfortran.dg/finalize_2.f03 index b91bedff81f3..37b532efcb99 100644 --- a/gcc/testsuite/gfortran.dg/finalize_2.f03 +++ b/gcc/testsuite/gfortran.dg/finalize_2.f03 @@ -19,5 +19,3 @@ PROGRAM finalizer IMPLICIT NONE ! Do nothing here END PROGRAM finalizer - -! { dg-final { cleanup-modules "final_type" } } diff --git a/gcc/testsuite/gfortran.dg/finalize_3.f03 b/gcc/testsuite/gfortran.dg/finalize_3.f03 index edc493bfca51..0d7d34cdeba6 100644 --- a/gcc/testsuite/gfortran.dg/finalize_3.f03 +++ b/gcc/testsuite/gfortran.dg/finalize_3.f03 @@ -21,5 +21,3 @@ PROGRAM finalizer IMPLICIT NONE ! Do nothing here END PROGRAM finalizer - -! { dg-final { cleanup-modules "final_type" } } diff --git a/gcc/testsuite/gfortran.dg/finalize_4.f03 b/gcc/testsuite/gfortran.dg/finalize_4.f03 index 6e99256c2524..11e094f0d8f7 100644 --- a/gcc/testsuite/gfortran.dg/finalize_4.f03 +++ b/gcc/testsuite/gfortran.dg/finalize_4.f03 @@ -51,5 +51,3 @@ END PROGRAM finalizer ! TODO: Remove this once finalization is implemented. ! { dg-excess-errors "not yet implemented" } - -! { dg-final { cleanup-modules "final_type" } } diff --git a/gcc/testsuite/gfortran.dg/finalize_5.f03 b/gcc/testsuite/gfortran.dg/finalize_5.f03 index 1df2d8cf285f..b9ec3768fe4b 100644 --- a/gcc/testsuite/gfortran.dg/finalize_5.f03 +++ b/gcc/testsuite/gfortran.dg/finalize_5.f03 @@ -110,5 +110,3 @@ END PROGRAM finalizer ! TODO: Remove this once finalization is implemented. ! { dg-excess-errors "not yet implemented" } - -! { dg-final { cleanup-modules "final_type" } } diff --git a/gcc/testsuite/gfortran.dg/finalize_6.f90 b/gcc/testsuite/gfortran.dg/finalize_6.f90 index e790f4efb105..82d662f8c8d5 100644 --- a/gcc/testsuite/gfortran.dg/finalize_6.f90 +++ b/gcc/testsuite/gfortran.dg/finalize_6.f90 @@ -31,5 +31,3 @@ END PROGRAM finalizer ! TODO: Remove this once finalization is implemented. ! { dg-excess-errors "not yet implemented" } - -! { dg-final { cleanup-modules "final_type" } } diff --git a/gcc/testsuite/gfortran.dg/finalize_7.f03 b/gcc/testsuite/gfortran.dg/finalize_7.f03 index db6b4bea948a..6ca4f55db7a6 100644 --- a/gcc/testsuite/gfortran.dg/finalize_7.f03 +++ b/gcc/testsuite/gfortran.dg/finalize_7.f03 @@ -55,5 +55,3 @@ END PROGRAM finalizer ! TODO: Remove this once finalization is implemented. ! { dg-excess-errors "not yet implemented" } - -! { dg-final { cleanup-modules "final_type" } } diff --git a/gcc/testsuite/gfortran.dg/finalize_8.f03 b/gcc/testsuite/gfortran.dg/finalize_8.f03 index 6a4a135e0da0..b2027a0ba6dd 100644 --- a/gcc/testsuite/gfortran.dg/finalize_8.f03 +++ b/gcc/testsuite/gfortran.dg/finalize_8.f03 @@ -33,5 +33,3 @@ PROGRAM finalizer IMPLICIT NONE ! Do nothing here END PROGRAM finalizer - -! { dg-final { cleanup-modules "final_type" } } diff --git a/gcc/testsuite/gfortran.dg/forall_4.f90 b/gcc/testsuite/gfortran.dg/forall_4.f90 index e71e0b847f5e..0b0d73165073 100644 --- a/gcc/testsuite/gfortran.dg/forall_4.f90 +++ b/gcc/testsuite/gfortran.dg/forall_4.f90 @@ -64,4 +64,3 @@ contains w = 5 - i end function w end -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/forall_5.f90 b/gcc/testsuite/gfortran.dg/forall_5.f90 index 1d9efb904a9f..43ed2b5c3136 100644 --- a/gcc/testsuite/gfortran.dg/forall_5.f90 +++ b/gcc/testsuite/gfortran.dg/forall_5.f90 @@ -38,4 +38,3 @@ contains w = 5 - i end function w end -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/func_assign.f90 b/gcc/testsuite/gfortran.dg/func_assign.f90 index 430198b81395..7ecf32941ca7 100644 --- a/gcc/testsuite/gfortran.dg/func_assign.f90 +++ b/gcc/testsuite/gfortran.dg/func_assign.f90 @@ -31,5 +31,3 @@ contains end module mod end - -! { dg-final { cleanup-modules "mod" } } diff --git a/gcc/testsuite/gfortran.dg/func_assign_3.f90 b/gcc/testsuite/gfortran.dg/func_assign_3.f90 index 7846c8781363..db81adf8ec04 100644 --- a/gcc/testsuite/gfortran.dg/func_assign_3.f90 +++ b/gcc/testsuite/gfortran.dg/func_assign_3.f90 @@ -29,4 +29,3 @@ program bugTest testCatch = testObj%test(2,2) ! This would cause an ICE if (any (testCatch .ne. dble (reshape ([(i, i = 1, 4)],[2,2])))) call abort end program bugTest -! { dg-final { cleanup-modules "bugtestmod" } } diff --git a/gcc/testsuite/gfortran.dg/func_derived_1.f90 b/gcc/testsuite/gfortran.dg/func_derived_1.f90 index 2cf8e449c7e6..c8820aac3bbb 100644 --- a/gcc/testsuite/gfortran.dg/func_derived_1.f90 +++ b/gcc/testsuite/gfortran.dg/func_derived_1.f90 @@ -38,5 +38,3 @@ function f(i,x,c,arr) end function f end - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/func_derived_2.f90 b/gcc/testsuite/gfortran.dg/func_derived_2.f90 index 35860182a311..d79f120b054e 100644 --- a/gcc/testsuite/gfortran.dg/func_derived_2.f90 +++ b/gcc/testsuite/gfortran.dg/func_derived_2.f90 @@ -38,5 +38,3 @@ program func_derived_2 y => get2 (x) if (y%i.ne.112) call abort () end program func_derived_2 - -! { dg-final { cleanup-modules "mpoint" } } diff --git a/gcc/testsuite/gfortran.dg/func_derived_3.f90 b/gcc/testsuite/gfortran.dg/func_derived_3.f90 index 6facf218e091..a271fe98f6e4 100644 --- a/gcc/testsuite/gfortran.dg/func_derived_3.f90 +++ b/gcc/testsuite/gfortran.dg/func_derived_3.f90 @@ -123,5 +123,3 @@ end module func_derived_3a if (trim (line).ne."simple = 1") call abort () close (10) end program - -! { dg-final { cleanup-modules "func_derived_3 func_derived_3a" } } diff --git a/gcc/testsuite/gfortran.dg/func_derived_4.f90 b/gcc/testsuite/gfortran.dg/func_derived_4.f90 index 532d821deefb..03560230dd08 100644 --- a/gcc/testsuite/gfortran.dg/func_derived_4.f90 +++ b/gcc/testsuite/gfortran.dg/func_derived_4.f90 @@ -101,5 +101,3 @@ program test_pnt call create_field(quality,msh) mshp => msh_(quality) end program test_pnt - -! { dg-final { cleanup-modules "class_mesh class_field class_scalar_field" } } diff --git a/gcc/testsuite/gfortran.dg/func_derived_5.f90 b/gcc/testsuite/gfortran.dg/func_derived_5.f90 index 76d45a883d82..d4e7b7c73b11 100644 --- a/gcc/testsuite/gfortran.dg/func_derived_5.f90 +++ b/gcc/testsuite/gfortran.dg/func_derived_5.f90 @@ -10,5 +10,3 @@ type(t) function foo() use m foo = t() end function foo - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/func_result_6.f90 b/gcc/testsuite/gfortran.dg/func_result_6.f90 index e64a2ef7abc8..48b34f3b709a 100644 --- a/gcc/testsuite/gfortran.dg/func_result_6.f90 +++ b/gcc/testsuite/gfortran.dg/func_result_6.f90 @@ -69,5 +69,3 @@ contains foo = [33, 77] end function foo end subroutine test - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/function_charlen_1.f90 b/gcc/testsuite/gfortran.dg/function_charlen_1.f90 index e0ecc63b89f6..40f602f25fc6 100644 --- a/gcc/testsuite/gfortran.dg/function_charlen_1.f90 +++ b/gcc/testsuite/gfortran.dg/function_charlen_1.f90 @@ -20,4 +20,3 @@ end function test end interface print *, test() end -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/function_charlen_2.f90 b/gcc/testsuite/gfortran.dg/function_charlen_2.f90 index 84d3d7e953ac..5713c307bd99 100644 --- a/gcc/testsuite/gfortran.dg/function_charlen_2.f90 +++ b/gcc/testsuite/gfortran.dg/function_charlen_2.f90 @@ -28,4 +28,3 @@ contains if (len (g) == 2) g= "2" end function g end program test -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/function_kinds_1.f90 b/gcc/testsuite/gfortran.dg/function_kinds_1.f90 index f0140df0620c..7d143740c249 100644 --- a/gcc/testsuite/gfortran.dg/function_kinds_1.f90 +++ b/gcc/testsuite/gfortran.dg/function_kinds_1.f90 @@ -51,4 +51,3 @@ end module mymodule z = func() if (z%i .ne. 5) call abort () end -! { dg-final { cleanup-modules "kinds mymodule" } } diff --git a/gcc/testsuite/gfortran.dg/function_kinds_2.f90 b/gcc/testsuite/gfortran.dg/function_kinds_2.f90 index f14453df9b2e..8282f0127830 100644 --- a/gcc/testsuite/gfortran.dg/function_kinds_2.f90 +++ b/gcc/testsuite/gfortran.dg/function_kinds_2.f90 @@ -17,5 +17,3 @@ module x end function end interface end module -! { dg-final { cleanup-modules "types x" } } - diff --git a/gcc/testsuite/gfortran.dg/function_kinds_3.f90 b/gcc/testsuite/gfortran.dg/function_kinds_3.f90 index b1dd2b4a2d00..db95729690b3 100644 --- a/gcc/testsuite/gfortran.dg/function_kinds_3.f90 +++ b/gcc/testsuite/gfortran.dg/function_kinds_3.f90 @@ -27,5 +27,3 @@ character(1,kind=char_t) function test4() use m test4 = 'A' end function test4 - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/function_kinds_4.f90 b/gcc/testsuite/gfortran.dg/function_kinds_4.f90 index bcde1e4478e2..d0e48f6b4d24 100644 --- a/gcc/testsuite/gfortran.dg/function_kinds_4.f90 +++ b/gcc/testsuite/gfortran.dg/function_kinds_4.f90 @@ -53,4 +53,3 @@ contains two = 1 end function two end program main -! { dg-final { cleanup-modules "m1 m2" } } diff --git a/gcc/testsuite/gfortran.dg/function_optimize_8.f90 b/gcc/testsuite/gfortran.dg/function_optimize_8.f90 index c197a6d7ff54..56e48c50347e 100644 --- a/gcc/testsuite/gfortran.dg/function_optimize_8.f90 +++ b/gcc/testsuite/gfortran.dg/function_optimize_8.f90 @@ -33,4 +33,3 @@ end program main ! { dg-final { scan-tree-dump-times "myfunc" 2 "original" } } ! { dg-final { scan-tree-dump-times "mychar" 2 "original" } } ! { dg-final { cleanup-tree-dump "original" } } -! { dg-final { cleanup-modules "x" } } diff --git a/gcc/testsuite/gfortran.dg/function_types_1.f90 b/gcc/testsuite/gfortran.dg/function_types_1.f90 index fb18d2f0e505..f56884f93ae1 100644 --- a/gcc/testsuite/gfortran.dg/function_types_1.f90 +++ b/gcc/testsuite/gfortran.dg/function_types_1.f90 @@ -9,4 +9,3 @@ contains type(non_exist) function func2() ! { dg-error "not accessible" } end function func2 end module bar -! { dg-final { cleanup-modules "bar" } } diff --git a/gcc/testsuite/gfortran.dg/function_types_2.f90 b/gcc/testsuite/gfortran.dg/function_types_2.f90 index b3b5a0aee9c6..0c1603939448 100644 --- a/gcc/testsuite/gfortran.dg/function_types_2.f90 +++ b/gcc/testsuite/gfortran.dg/function_types_2.f90 @@ -101,4 +101,3 @@ contains d1%m = 55 end function d1 end program main -! { dg-final { cleanup-modules "m1 m2 m3" } } diff --git a/gcc/testsuite/gfortran.dg/generic_1.f90 b/gcc/testsuite/gfortran.dg/generic_1.f90 index 6a7a6df4a0b1..1cbf4bb8cbcb 100644 --- a/gcc/testsuite/gfortran.dg/generic_1.f90 +++ b/gcc/testsuite/gfortran.dg/generic_1.f90 @@ -17,5 +17,3 @@ end module subroutine BAZ(X) use FOO end subroutine - -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/generic_10.f90 b/gcc/testsuite/gfortran.dg/generic_10.f90 index 8f9ff6fcbe82..6684c4ff8507 100644 --- a/gcc/testsuite/gfortran.dg/generic_10.f90 +++ b/gcc/testsuite/gfortran.dg/generic_10.f90 @@ -33,4 +33,3 @@ end module gfcbug46 call random_number (z) print *, z end -! { dg-final { cleanup-modules "gfcbug46" } } diff --git a/gcc/testsuite/gfortran.dg/generic_11.f90 b/gcc/testsuite/gfortran.dg/generic_11.f90 index 7547a43da76f..decc0aeebbae 100644 --- a/gcc/testsuite/gfortran.dg/generic_11.f90 +++ b/gcc/testsuite/gfortran.dg/generic_11.f90 @@ -26,6 +26,3 @@ use m_bar call foo ! { dg-error "is an ambiguous reference" } end -! { dg-final { cleanup-modules "m_foo m_bar" } } - - diff --git a/gcc/testsuite/gfortran.dg/generic_12.f90 b/gcc/testsuite/gfortran.dg/generic_12.f90 index 59c3c96e3e29..007f3ee4c99f 100644 --- a/gcc/testsuite/gfortran.dg/generic_12.f90 +++ b/gcc/testsuite/gfortran.dg/generic_12.f90 @@ -29,4 +29,3 @@ PROGRAM main IMPLICIT NONE CALL hello(10) END PROGRAM main -! { dg-final { cleanup-modules "interfaces global_module" } } diff --git a/gcc/testsuite/gfortran.dg/generic_13.f90 b/gcc/testsuite/gfortran.dg/generic_13.f90 index 56613451115f..58b886d9d4d1 100644 --- a/gcc/testsuite/gfortran.dg/generic_13.f90 +++ b/gcc/testsuite/gfortran.dg/generic_13.f90 @@ -33,4 +33,3 @@ PROGRAM TT CALL SUB(xx,I) IF (I.NE.7) CALL ABORT() END PROGRAM -! { dg-final { cleanup-modules "test too" } } diff --git a/gcc/testsuite/gfortran.dg/generic_14.f90 b/gcc/testsuite/gfortran.dg/generic_14.f90 index e95f6f2edebc..5636e9a5d2c8 100644 --- a/gcc/testsuite/gfortran.dg/generic_14.f90 +++ b/gcc/testsuite/gfortran.dg/generic_14.f90 @@ -101,5 +101,3 @@ module h end module h end - -! { dg-final { cleanup-modules "a inclmod" } } diff --git a/gcc/testsuite/gfortran.dg/generic_15.f90 b/gcc/testsuite/gfortran.dg/generic_15.f90 index 127868473ff9..179d04a53cc7 100644 --- a/gcc/testsuite/gfortran.dg/generic_15.f90 +++ b/gcc/testsuite/gfortran.dg/generic_15.f90 @@ -41,4 +41,3 @@ PROGRAM main CALL odfname(base,i,cnames) if (trim (cnames(1)) .ne. "odfamilycnames") call abort END PROGRAM -! { dg-final { cleanup-modules "test" } } diff --git a/gcc/testsuite/gfortran.dg/generic_16.f90 b/gcc/testsuite/gfortran.dg/generic_16.f90 index 501e146bcc1d..cb6e34df554e 100644 --- a/gcc/testsuite/gfortran.dg/generic_16.f90 +++ b/gcc/testsuite/gfortran.dg/generic_16.f90 @@ -32,4 +32,3 @@ PROGRAM main REAL(kind=dp) :: rawData(2), data, work(3) data = median(rawData, work) ! { dg-error "no specific function" } END PROGRAM main -! { dg-final { cleanup-modules "auxiliary" } } diff --git a/gcc/testsuite/gfortran.dg/generic_17.f90 b/gcc/testsuite/gfortran.dg/generic_17.f90 index 0e9a41d5b027..bd919bcb364f 100644 --- a/gcc/testsuite/gfortran.dg/generic_17.f90 +++ b/gcc/testsuite/gfortran.dg/generic_17.f90 @@ -37,4 +37,3 @@ end module foo_mod subroutine s_foobar2(x) use foo_mod end subroutine s_foobar2 -! { dg-final { cleanup-modules "s_foo_mod d_foo_mod foo_mod" } } diff --git a/gcc/testsuite/gfortran.dg/generic_18.f90 b/gcc/testsuite/gfortran.dg/generic_18.f90 index 695262b304b0..8bfd770b9bfc 100644 --- a/gcc/testsuite/gfortran.dg/generic_18.f90 +++ b/gcc/testsuite/gfortran.dg/generic_18.f90 @@ -51,4 +51,3 @@ END PROGRAM MakeAChoice ! { dg-final { scan-tree-dump-times "specproc" 3 "original" } } ! { dg-final { scan-tree-dump-times "elemproc" 3 "original" } } ! { dg-final { cleanup-tree-dump "original" } } -! { dg-final { cleanup-modules "someoptions" } } diff --git a/gcc/testsuite/gfortran.dg/generic_19.f90 b/gcc/testsuite/gfortran.dg/generic_19.f90 index f023c5e63565..8bbbf8a0ee1b 100644 --- a/gcc/testsuite/gfortran.dg/generic_19.f90 +++ b/gcc/testsuite/gfortran.dg/generic_19.f90 @@ -34,4 +34,3 @@ program prog call sub(1, "integer ") call sub(1.0, "real ") end program prog -! { dg-final { cleanup-modules "mod1 mod2" } } diff --git a/gcc/testsuite/gfortran.dg/generic_2.f90 b/gcc/testsuite/gfortran.dg/generic_2.f90 index 459dd7ec8173..802e966c4baf 100644 --- a/gcc/testsuite/gfortran.dg/generic_2.f90 +++ b/gcc/testsuite/gfortran.dg/generic_2.f90 @@ -18,5 +18,3 @@ end module bidon integer,intent(in) :: nspden end subroutine nonlinear - -! { dg-final { cleanup-modules "bidon" } } diff --git a/gcc/testsuite/gfortran.dg/generic_20.f90 b/gcc/testsuite/gfortran.dg/generic_20.f90 index 04a57b09057b..83485b6f7b92 100644 --- a/gcc/testsuite/gfortran.dg/generic_20.f90 +++ b/gcc/testsuite/gfortran.dg/generic_20.f90 @@ -27,5 +27,3 @@ real :: res(1) res = matmul (one(2.0), (/ 2.0/)) if (abs (res(1)-4.0) > epsilon (res)) call abort () end - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/generic_21.f90 b/gcc/testsuite/gfortran.dg/generic_21.f90 index c651e6394279..b11aa7facf0b 100644 --- a/gcc/testsuite/gfortran.dg/generic_21.f90 +++ b/gcc/testsuite/gfortran.dg/generic_21.f90 @@ -29,5 +29,3 @@ contains end do end function sqrt_vector end module gfcbug102 - -! { dg-final { cleanup-modules "gfcbug102" } } diff --git a/gcc/testsuite/gfortran.dg/generic_22.f03 b/gcc/testsuite/gfortran.dg/generic_22.f03 index 487d93c511b7..040fddd95f0b 100644 --- a/gcc/testsuite/gfortran.dg/generic_22.f03 +++ b/gcc/testsuite/gfortran.dg/generic_22.f03 @@ -35,4 +35,3 @@ contains end module base_mod -! { dg-final { cleanup-modules "base_mod" } } diff --git a/gcc/testsuite/gfortran.dg/generic_23.f03 b/gcc/testsuite/gfortran.dg/generic_23.f03 index eab185b483dc..94dbbbcc163b 100644 --- a/gcc/testsuite/gfortran.dg/generic_23.f03 +++ b/gcc/testsuite/gfortran.dg/generic_23.f03 @@ -63,5 +63,3 @@ program testd15 if (af2%get() .ne. 3) call abort end program testd15 - -! { dg-final { cleanup-modules "foo_mod foo2_mod" } } diff --git a/gcc/testsuite/gfortran.dg/generic_24.f90 b/gcc/testsuite/gfortran.dg/generic_24.f90 index 2388722b55b4..18ca81ced909 100644 --- a/gcc/testsuite/gfortran.dg/generic_24.f90 +++ b/gcc/testsuite/gfortran.dg/generic_24.f90 @@ -96,5 +96,3 @@ program test use sparse_matrices_fields use global_numbering end program test - -! { dg-final { cleanup-modules "sparse_tools sparse_matrices_fields global_numbering" } } diff --git a/gcc/testsuite/gfortran.dg/generic_3.f90 b/gcc/testsuite/gfortran.dg/generic_3.f90 index 549260385156..3cd2e9d5d556 100644 --- a/gcc/testsuite/gfortran.dg/generic_3.f90 +++ b/gcc/testsuite/gfortran.dg/generic_3.f90 @@ -28,5 +28,3 @@ subroutine mrqcof( x, y, sig, ndata, a, ia, ma ) call gauss( x(i), a, yan, dyda, ma ) end do end subroutine mrqcof - -! { dg-final { cleanup-modules "fit_functions" } } diff --git a/gcc/testsuite/gfortran.dg/generic_4.f90 b/gcc/testsuite/gfortran.dg/generic_4.f90 index 53cf90032821..62bc569a21c2 100644 --- a/gcc/testsuite/gfortran.dg/generic_4.f90 +++ b/gcc/testsuite/gfortran.dg/generic_4.f90 @@ -26,5 +26,3 @@ y = (/1,2,3/) call baz(y,z) if (any (y /= z)) call abort () end - -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/generic_5.f90 b/gcc/testsuite/gfortran.dg/generic_5.f90 index cb720980341a..f7a9a9715586 100644 --- a/gcc/testsuite/gfortran.dg/generic_5.f90 +++ b/gcc/testsuite/gfortran.dg/generic_5.f90 @@ -26,4 +26,3 @@ CONTAINS CALL ice(23.0) ! { dg-error "no specific subroutine" } END SUBROUTINE END MODULE -! { dg-final { cleanup-modules "ice_gfortran provoke_ice" } } diff --git a/gcc/testsuite/gfortran.dg/generic_6.f90 b/gcc/testsuite/gfortran.dg/generic_6.f90 index 928861e3e992..5a8bc03f1170 100644 --- a/gcc/testsuite/gfortran.dg/generic_6.f90 +++ b/gcc/testsuite/gfortran.dg/generic_6.f90 @@ -46,4 +46,3 @@ end module use c call useCreate end -! { dg-final { cleanup-modules "a b c" } } diff --git a/gcc/testsuite/gfortran.dg/generic_7.f90 b/gcc/testsuite/gfortran.dg/generic_7.f90 index e520c0973aeb..7b9db24d5ba1 100644 --- a/gcc/testsuite/gfortran.dg/generic_7.f90 +++ b/gcc/testsuite/gfortran.dg/generic_7.f90 @@ -24,5 +24,3 @@ CONTAINS WRITE(*,*) x, y END SUBROUTINE END MODULE - -! { dg-final { cleanup-modules "global" } } diff --git a/gcc/testsuite/gfortran.dg/generic_8.f90 b/gcc/testsuite/gfortran.dg/generic_8.f90 index a129efe4ca47..c84396be8ac2 100644 --- a/gcc/testsuite/gfortran.dg/generic_8.f90 +++ b/gcc/testsuite/gfortran.dg/generic_8.f90 @@ -28,4 +28,3 @@ CONTAINS CALL A(MAXVAL(X),Y) END SUBROUTINE T END MODULE M -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/generic_9.f90 b/gcc/testsuite/gfortran.dg/generic_9.f90 index 92dd65096c1a..6ecd5bdbbf89 100644 --- a/gcc/testsuite/gfortran.dg/generic_9.f90 +++ b/gcc/testsuite/gfortran.dg/generic_9.f90 @@ -42,4 +42,3 @@ contains END SUBROUTINE END MODULE -! { dg-final { cleanup-modules "class_foo_type class_foo" } } diff --git a/gcc/testsuite/gfortran.dg/generic_actual_arg.f90 b/gcc/testsuite/gfortran.dg/generic_actual_arg.f90 index 3f328c95b0f0..9c1fc3e728a4 100644 --- a/gcc/testsuite/gfortran.dg/generic_actual_arg.f90 +++ b/gcc/testsuite/gfortran.dg/generic_actual_arg.f90 @@ -42,4 +42,3 @@ END SUBROUTINE F() END SUBROUTINE -! { dg-final { cleanup-modules "test test2" } } diff --git a/gcc/testsuite/gfortran.dg/generic_typebound_operator_1.f90 b/gcc/testsuite/gfortran.dg/generic_typebound_operator_1.f90 index 32a17e3bd8a4..76c15e97baa1 100644 --- a/gcc/testsuite/gfortran.dg/generic_typebound_operator_1.f90 +++ b/gcc/testsuite/gfortran.dg/generic_typebound_operator_1.f90 @@ -17,5 +17,3 @@ module m_sort end function gt_cmp end interface end module m_sort - -! { dg-final { cleanup-modules "m_sort" } } diff --git a/gcc/testsuite/gfortran.dg/global_references_1.f90 b/gcc/testsuite/gfortran.dg/global_references_1.f90 index 7e0a5bd0a34d..5e72dc9419be 100644 --- a/gcc/testsuite/gfortran.dg/global_references_1.f90 +++ b/gcc/testsuite/gfortran.dg/global_references_1.f90 @@ -96,5 +96,3 @@ END SUBROUTINE j entry link2 (nameg) ! { dg-error "is already being used as a SUBROUTINE" } return end - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/global_vars_c_init.f90 b/gcc/testsuite/gfortran.dg/global_vars_c_init.f90 index 15f28f5bd2d7..60408083951c 100644 --- a/gcc/testsuite/gfortran.dg/global_vars_c_init.f90 +++ b/gcc/testsuite/gfortran.dg/global_vars_c_init.f90 @@ -14,5 +14,3 @@ contains endif end subroutine test_globals end module global_vars_c_init - -! { dg-final { cleanup-modules "global_vars_c_init" } } diff --git a/gcc/testsuite/gfortran.dg/global_vars_f90_init.f90 b/gcc/testsuite/gfortran.dg/global_vars_f90_init.f90 index aa1a60ba406c..7702f3dbb720 100644 --- a/gcc/testsuite/gfortran.dg/global_vars_f90_init.f90 +++ b/gcc/testsuite/gfortran.dg/global_vars_f90_init.f90 @@ -14,5 +14,3 @@ contains endif end subroutine test_globals end module global_vars_f90_init - -! { dg-final { cleanup-modules "global_vars_f90_init" } } diff --git a/gcc/testsuite/gfortran.dg/gomp/allocatable_components_1.f90 b/gcc/testsuite/gfortran.dg/gomp/allocatable_components_1.f90 index 225d0a2b5ed3..2a762c77bac6 100644 --- a/gcc/testsuite/gfortran.dg/gomp/allocatable_components_1.f90 +++ b/gcc/testsuite/gfortran.dg/gomp/allocatable_components_1.f90 @@ -55,5 +55,3 @@ CONTAINS !$omp end parallel do END SUBROUTINE END MODULE - -! { dg-final { cleanup-modules "test_allocatable_components" } } diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.22.4.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.22.4.f90 index 2a637580ba7a..f769fc18f3e7 100644 --- a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.22.4.f90 +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.22.4.f90 @@ -9,4 +9,3 @@ !$OMP THREADPRIVATE(/T/) ! { dg-error "COMMON block" } !non-conforming because /T/ not declared in A22_4_WRONG END SUBROUTINE A22_4_WRONG -! { dg-final { cleanup-modules "A22_MODULE" } } diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.26.2.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.26.2.f90 index 3d43424b605c..97c14d945d1d 100644 --- a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.26.2.f90 +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.26.2.f90 @@ -20,4 +20,3 @@ !$OMP END PARALLEL DO END SUBROUTINE F END MODULE A26_2 -! { dg-final { cleanup-modules "A26_2" } } diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.32.1.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.32.1.f90 index 498a6d324a6b..8e0b5e093c57 100644 --- a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.32.1.f90 +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.32.1.f90 @@ -22,4 +22,3 @@ ALLOCATE(WORK(SIZE)) WORK = TOL END SUBROUTINE BUILD -! { dg-final { cleanup-modules "M" } } diff --git a/gcc/testsuite/gfortran.dg/gomp/omp_threadprivate1.f90 b/gcc/testsuite/gfortran.dg/gomp/omp_threadprivate1.f90 index 2ccf93caca56..55aad067082e 100644 --- a/gcc/testsuite/gfortran.dg/gomp/omp_threadprivate1.f90 +++ b/gcc/testsuite/gfortran.dg/gomp/omp_threadprivate1.f90 @@ -15,4 +15,3 @@ !$omp end parallel ! { dg-error "" } end subroutine bad3 end subroutine bad2 -! { dg-final { cleanup-modules "omp_threadprivate1" } } diff --git a/gcc/testsuite/gfortran.dg/gomp/pr35786-1.f90 b/gcc/testsuite/gfortran.dg/gomp/pr35786-1.f90 index c8639abdbbd0..ab72f066c496 100644 --- a/gcc/testsuite/gfortran.dg/gomp/pr35786-1.f90 +++ b/gcc/testsuite/gfortran.dg/gomp/pr35786-1.f90 @@ -70,5 +70,3 @@ contains end subroutine fn14 end function fn12 end module - -! { dg-final { cleanup-modules "pr35768" } } diff --git a/gcc/testsuite/gfortran.dg/gomp/reduction3.f90 b/gcc/testsuite/gfortran.dg/gomp/reduction3.f90 index 0272a7415960..2c113893af94 100644 --- a/gcc/testsuite/gfortran.dg/gomp/reduction3.f90 +++ b/gcc/testsuite/gfortran.dg/gomp/reduction3.f90 @@ -62,4 +62,3 @@ subroutine f6 i = iand (i, 18) !$omp end parallel end subroutine f6 -! { dg-final { cleanup-modules "mreduction3" } } diff --git a/gcc/testsuite/gfortran.dg/graphite/id-18.f90 b/gcc/testsuite/gfortran.dg/graphite/id-18.f90 index ed780673655c..273e670fcee8 100644 --- a/gcc/testsuite/gfortran.dg/graphite/id-18.f90 +++ b/gcc/testsuite/gfortran.dg/graphite/id-18.f90 @@ -23,4 +23,3 @@ CONTAINS END SELECT END FUNCTION dlegendre END MODULE spherical_harmonics -! { dg-final { cleanup-modules "spherical_harmonics" } } diff --git a/gcc/testsuite/gfortran.dg/graphite/id-2.f90 b/gcc/testsuite/gfortran.dg/graphite/id-2.f90 index 2f9f9dbec372..720fff8dd02a 100644 --- a/gcc/testsuite/gfortran.dg/graphite/id-2.f90 +++ b/gcc/testsuite/gfortran.dg/graphite/id-2.f90 @@ -11,4 +11,3 @@ contains subroutine fourir(A,ntot,kconjg, E,useold) end subroutine fourir end module solv_cap -! { dg-final { cleanup-modules "solv_cap" } } diff --git a/gcc/testsuite/gfortran.dg/graphite/id-21.f b/gcc/testsuite/gfortran.dg/graphite/id-21.f index e75193411fc7..4fa047ed6f28 100644 --- a/gcc/testsuite/gfortran.dg/graphite/id-21.f +++ b/gcc/testsuite/gfortran.dg/graphite/id-21.f @@ -18,5 +18,3 @@ END DO ENDDO END - -! { dg-final { cleanup-modules "les3d_data" } } diff --git a/gcc/testsuite/gfortran.dg/graphite/id-4.f90 b/gcc/testsuite/gfortran.dg/graphite/id-4.f90 index 83899445de41..b2c6cb04edc5 100644 --- a/gcc/testsuite/gfortran.dg/graphite/id-4.f90 +++ b/gcc/testsuite/gfortran.dg/graphite/id-4.f90 @@ -30,4 +30,3 @@ CONTAINS END IF END SUBROUTINE QSORT END SUBROUTINE READIN -! { dg-final { cleanup-modules "vimage vcimage" } } diff --git a/gcc/testsuite/gfortran.dg/graphite/pr37980.f90 b/gcc/testsuite/gfortran.dg/graphite/pr37980.f90 index e964adec1b8e..62eccf35ff1d 100644 --- a/gcc/testsuite/gfortran.dg/graphite/pr37980.f90 +++ b/gcc/testsuite/gfortran.dg/graphite/pr37980.f90 @@ -9,4 +9,3 @@ contains mat0 = 0.0d0 end function spher_cartesians end module INT_MODULE -! { dg-final { cleanup-modules "int_module" } } diff --git a/gcc/testsuite/gfortran.dg/graphite/pr38953.f90 b/gcc/testsuite/gfortran.dg/graphite/pr38953.f90 index 391549e3cd01..73224764f16d 100644 --- a/gcc/testsuite/gfortran.dg/graphite/pr38953.f90 +++ b/gcc/testsuite/gfortran.dg/graphite/pr38953.f90 @@ -113,4 +113,3 @@ ENDIF 999 CONTINUE END -! { dg-final { cleanup-modules "main1" } } diff --git a/gcc/testsuite/gfortran.dg/graphite/pr40982.f90 b/gcc/testsuite/gfortran.dg/graphite/pr40982.f90 index c49def850bf5..b9641aef0311 100644 --- a/gcc/testsuite/gfortran.dg/graphite/pr40982.f90 +++ b/gcc/testsuite/gfortran.dg/graphite/pr40982.f90 @@ -67,5 +67,3 @@ contains end subroutine mutual_ind_quad_cir_coil end module mqc_m -! { dg-final { cleanup-modules "mqc_m" } } - diff --git a/gcc/testsuite/gfortran.dg/graphite/pr41924.f90 b/gcc/testsuite/gfortran.dg/graphite/pr41924.f90 index 2f248d0b8928..f8dc8078e5ce 100644 --- a/gcc/testsuite/gfortran.dg/graphite/pr41924.f90 +++ b/gcc/testsuite/gfortran.dg/graphite/pr41924.f90 @@ -13,4 +13,3 @@ SUBROUTINE VOLCALC() IF ( WETSCIM ) HRVALD(ITYP) = 0.0 ENDDO END SUBROUTINE VOLCALC -! { dg-final { cleanup-modules "main1" } } diff --git a/gcc/testsuite/gfortran.dg/graphite/pr42050.f90 b/gcc/testsuite/gfortran.dg/graphite/pr42050.f90 index e019917414c9..09cab6f0f1c6 100644 --- a/gcc/testsuite/gfortran.dg/graphite/pr42050.f90 +++ b/gcc/testsuite/gfortran.dg/graphite/pr42050.f90 @@ -23,4 +23,3 @@ CONTAINS CALL test() END SUBROUTINE sic_explicit_orbitals END MODULE qs_ks_methods -! { dg-final { cleanup-modules "qs_ks_methods" } } diff --git a/gcc/testsuite/gfortran.dg/graphite/pr42180.f90 b/gcc/testsuite/gfortran.dg/graphite/pr42180.f90 index bb5bc0c58db0..523c479e215a 100644 --- a/gcc/testsuite/gfortran.dg/graphite/pr42180.f90 +++ b/gcc/testsuite/gfortran.dg/graphite/pr42180.f90 @@ -20,4 +20,3 @@ contains l12 = coefficient * l12 end subroutine mutual_ind_cir_cir_coils end module mcc_m -! { dg-final { cleanup-modules "mcc_m" } } diff --git a/gcc/testsuite/gfortran.dg/graphite/pr42181.f90 b/gcc/testsuite/gfortran.dg/graphite/pr42181.f90 index 06ce47d9e7f6..dafb63fdc8b1 100644 --- a/gcc/testsuite/gfortran.dg/graphite/pr42181.f90 +++ b/gcc/testsuite/gfortran.dg/graphite/pr42181.f90 @@ -17,4 +17,3 @@ CONTAINS END IF END SUBROUTINE newuob END MODULE powell -! { dg-final { cleanup-modules "powell" } } diff --git a/gcc/testsuite/gfortran.dg/graphite/pr42185.f90 b/gcc/testsuite/gfortran.dg/graphite/pr42185.f90 index 6fa6e3036771..5002521ac4c9 100644 --- a/gcc/testsuite/gfortran.dg/graphite/pr42185.f90 +++ b/gcc/testsuite/gfortran.dg/graphite/pr42185.f90 @@ -25,4 +25,3 @@ CONTAINS END DO mainloop END SUBROUTINE trsapp END MODULE powell -! { dg-final { cleanup-modules "powell" } } diff --git a/gcc/testsuite/gfortran.dg/graphite/pr42186.f90 b/gcc/testsuite/gfortran.dg/graphite/pr42186.f90 index 0e3669bf5e7b..9e488f4f1893 100644 --- a/gcc/testsuite/gfortran.dg/graphite/pr42186.f90 +++ b/gcc/testsuite/gfortran.dg/graphite/pr42186.f90 @@ -12,4 +12,3 @@ CONTAINS END IF END SUBROUTINE CALERF END MODULE erf_fn -! { dg-final { cleanup-modules "erf_fn" } } diff --git a/gcc/testsuite/gfortran.dg/graphite/pr42393-1.f90 b/gcc/testsuite/gfortran.dg/graphite/pr42393-1.f90 index 45c635b761d7..fb62e20f45c8 100644 --- a/gcc/testsuite/gfortran.dg/graphite/pr42393-1.f90 +++ b/gcc/testsuite/gfortran.dg/graphite/pr42393-1.f90 @@ -22,4 +22,3 @@ CONTAINS fn_val = sum END FUNCTION basym END MODULE beta_gamma_psi -! { dg-final { cleanup-modules "beta_gamma_psi" } } diff --git a/gcc/testsuite/gfortran.dg/graphite/pr42393.f90 b/gcc/testsuite/gfortran.dg/graphite/pr42393.f90 index da9a348dd44d..1fc708ef9673 100644 --- a/gcc/testsuite/gfortran.dg/graphite/pr42393.f90 +++ b/gcc/testsuite/gfortran.dg/graphite/pr42393.f90 @@ -28,4 +28,3 @@ CONTAINS fn_val = e0*t*u*sum END FUNCTION basym END MODULE beta_gamma_psi -! { dg-final { cleanup-modules "beta_gamma_psi" } } diff --git a/gcc/testsuite/gfortran.dg/graphite/pr45758.f90 b/gcc/testsuite/gfortran.dg/graphite/pr45758.f90 index d6a197397e00..90baa4ccee98 100644 --- a/gcc/testsuite/gfortran.dg/graphite/pr45758.f90 +++ b/gcc/testsuite/gfortran.dg/graphite/pr45758.f90 @@ -38,4 +38,3 @@ CONTAINS ENDDO END SUBROUTINE create_destination_list END MODULE -! { dg-final { cleanup-modules "util" } } diff --git a/gcc/testsuite/gfortran.dg/host_assoc_blockdata_1.f90 b/gcc/testsuite/gfortran.dg/host_assoc_blockdata_1.f90 index 07f9ed478b26..7f24fecb0e00 100644 --- a/gcc/testsuite/gfortran.dg/host_assoc_blockdata_1.f90 +++ b/gcc/testsuite/gfortran.dg/host_assoc_blockdata_1.f90 @@ -9,4 +9,3 @@ END module globals BLOCK DATA use globals END BLOCK DATA -! { dg-final { cleanup-modules "globals" } } diff --git a/gcc/testsuite/gfortran.dg/host_assoc_blockdata_2.f90 b/gcc/testsuite/gfortran.dg/host_assoc_blockdata_2.f90 index 40e3ac4d5d40..3cb4abaedd23 100644 --- a/gcc/testsuite/gfortran.dg/host_assoc_blockdata_2.f90 +++ b/gcc/testsuite/gfortran.dg/host_assoc_blockdata_2.f90 @@ -15,4 +15,3 @@ program main use globals common /co/ pdm_bps ! { dg-error "already in a COMMON block" } end program main -! { dg-final { cleanup-modules "globals" } } diff --git a/gcc/testsuite/gfortran.dg/host_assoc_call_1.f90 b/gcc/testsuite/gfortran.dg/host_assoc_call_1.f90 index 804929080a18..df9951efe4f9 100644 --- a/gcc/testsuite/gfortran.dg/host_assoc_call_1.f90 +++ b/gcc/testsuite/gfortran.dg/host_assoc_call_1.f90 @@ -14,4 +14,3 @@ CONTAINS END SUBROUTINE sub2 END SUBROUTINE sub1 END MODULE ksbin2_aux_mod -! { dg-final { cleanup-modules "ksbin2_aux_mod" } } diff --git a/gcc/testsuite/gfortran.dg/host_assoc_call_2.f90 b/gcc/testsuite/gfortran.dg/host_assoc_call_2.f90 index 1175c46b31cb..7a6b64df9cff 100644 --- a/gcc/testsuite/gfortran.dg/host_assoc_call_2.f90 +++ b/gcc/testsuite/gfortran.dg/host_assoc_call_2.f90 @@ -15,4 +15,3 @@ contains call InitialDiatomicX () ! { dg-error "which is not consistent with the CALL" } end subroutine FindDiatomicPeriod end module Diatoms -! { dg-final { cleanup-modules "diatoms" } } diff --git a/gcc/testsuite/gfortran.dg/host_assoc_call_3.f90 b/gcc/testsuite/gfortran.dg/host_assoc_call_3.f90 index 28c55bfa5663..49dff0c5f611 100644 --- a/gcc/testsuite/gfortran.dg/host_assoc_call_3.f90 +++ b/gcc/testsuite/gfortran.dg/host_assoc_call_3.f90 @@ -52,4 +52,3 @@ END MODULE CALL S3 call S4 END -! { dg-final { cleanup-modules "m1 m2" } } diff --git a/gcc/testsuite/gfortran.dg/host_assoc_call_4.f90 b/gcc/testsuite/gfortran.dg/host_assoc_call_4.f90 index 50e1e3fce798..e5c8bde80145 100644 --- a/gcc/testsuite/gfortran.dg/host_assoc_call_4.f90 +++ b/gcc/testsuite/gfortran.dg/host_assoc_call_4.f90 @@ -45,4 +45,3 @@ contains call GetBasicElementData (TargetElement, ProcedureName, ErrorNumber, ErrorLevel, ErrorMessage, CallingStat) end subroutine WH_ERR end module ErrorMod -! { dg-final { cleanup-modules "errelmnt errormod" } } diff --git a/gcc/testsuite/gfortran.dg/host_assoc_call_5.f90 b/gcc/testsuite/gfortran.dg/host_assoc_call_5.f90 index 6ce57ce01906..a788be1926aa 100644 --- a/gcc/testsuite/gfortran.dg/host_assoc_call_5.f90 +++ b/gcc/testsuite/gfortran.dg/host_assoc_call_5.f90 @@ -18,4 +18,3 @@ contains subroutine other_sub () end subroutine other_sub end module foo -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/host_assoc_call_6.f90 b/gcc/testsuite/gfortran.dg/host_assoc_call_6.f90 index 60a5edc53c1d..da5cb374e91f 100644 --- a/gcc/testsuite/gfortran.dg/host_assoc_call_6.f90 +++ b/gcc/testsuite/gfortran.dg/host_assoc_call_6.f90 @@ -22,4 +22,3 @@ END MODULE USE m CALL g() END -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/host_assoc_function_1.f90 b/gcc/testsuite/gfortran.dg/host_assoc_function_1.f90 index f80f97a27ab5..dffaa93333a3 100644 --- a/gcc/testsuite/gfortran.dg/host_assoc_function_1.f90 +++ b/gcc/testsuite/gfortran.dg/host_assoc_function_1.f90 @@ -40,4 +40,3 @@ END MODULE use m call s() end -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/host_assoc_function_2.f90 b/gcc/testsuite/gfortran.dg/host_assoc_function_2.f90 index 5d63d7aa378f..f2a37b686970 100644 --- a/gcc/testsuite/gfortran.dg/host_assoc_function_2.f90 +++ b/gcc/testsuite/gfortran.dg/host_assoc_function_2.f90 @@ -45,4 +45,3 @@ contains end subroutine foo end module gfcbug64_mod2 -! { dg-final { cleanup-modules "gfcbug64_mod1 gfcbug64_mod2" } } diff --git a/gcc/testsuite/gfortran.dg/host_assoc_function_3.f90 b/gcc/testsuite/gfortran.dg/host_assoc_function_3.f90 index a83fa1738af5..cebe646fa583 100644 --- a/gcc/testsuite/gfortran.dg/host_assoc_function_3.f90 +++ b/gcc/testsuite/gfortran.dg/host_assoc_function_3.f90 @@ -24,4 +24,3 @@ END MODULE m use m call s end -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/host_assoc_function_4.f90 b/gcc/testsuite/gfortran.dg/host_assoc_function_4.f90 index 73ad21af91d5..46fb5f800626 100644 --- a/gcc/testsuite/gfortran.dg/host_assoc_function_4.f90 +++ b/gcc/testsuite/gfortran.dg/host_assoc_function_4.f90 @@ -27,4 +27,3 @@ END MODULE USE M2 CALL S2 END -! { dg-final { cleanup-modules "m1 m2" } } diff --git a/gcc/testsuite/gfortran.dg/host_assoc_function_5.f90 b/gcc/testsuite/gfortran.dg/host_assoc_function_5.f90 index c75202e445a9..4c5d17178af9 100644 --- a/gcc/testsuite/gfortran.dg/host_assoc_function_5.f90 +++ b/gcc/testsuite/gfortran.dg/host_assoc_function_5.f90 @@ -44,4 +44,3 @@ contains mons(1) = p1%mons(1)*p2%mons(2) end function end module -! { dg-final { cleanup-modules "mod_symmon mod_sympoly" } } diff --git a/gcc/testsuite/gfortran.dg/host_assoc_function_6.f90 b/gcc/testsuite/gfortran.dg/host_assoc_function_6.f90 index 28cd7c836996..5f4748f505a2 100644 --- a/gcc/testsuite/gfortran.dg/host_assoc_function_6.f90 +++ b/gcc/testsuite/gfortran.dg/host_assoc_function_6.f90 @@ -31,5 +31,3 @@ contains mu = a_fun(x) end function fun end module mod_b - -! { dg-final { cleanup-modules "mod_a mod_b" } } diff --git a/gcc/testsuite/gfortran.dg/host_assoc_function_7.f90 b/gcc/testsuite/gfortran.dg/host_assoc_function_7.f90 index 15684438a9f7..df240a9f985d 100644 --- a/gcc/testsuite/gfortran.dg/host_assoc_function_7.f90 +++ b/gcc/testsuite/gfortran.dg/host_assoc_function_7.f90 @@ -37,5 +37,3 @@ end module sa0054_stuff call SA0054 (RDA) IF (ANY (INT (RDA) .ne. [(6 * I, I = 1, 10)])) print *, rda END - -! { dg-final { cleanup-modules "sa0054_stuff" } } diff --git a/gcc/testsuite/gfortran.dg/host_assoc_function_9.f90 b/gcc/testsuite/gfortran.dg/host_assoc_function_9.f90 index 58cae435fb6b..1bdd6e842a5e 100644 --- a/gcc/testsuite/gfortran.dg/host_assoc_function_9.f90 +++ b/gcc/testsuite/gfortran.dg/host_assoc_function_9.f90 @@ -29,5 +29,3 @@ END MODULE use m call s end -! { dg-final { cleanup-modules "m" } } - diff --git a/gcc/testsuite/gfortran.dg/host_assoc_types_1.f90 b/gcc/testsuite/gfortran.dg/host_assoc_types_1.f90 index 53c968410e07..4a2377df0158 100644 --- a/gcc/testsuite/gfortran.dg/host_assoc_types_1.f90 +++ b/gcc/testsuite/gfortran.dg/host_assoc_types_1.f90 @@ -15,4 +15,3 @@ CONTAINS ENDDO vertex END SUBROUTINE END MODULE test -! { dg-final { cleanup-modules "test" } } diff --git a/gcc/testsuite/gfortran.dg/host_assoc_types_2.f90 b/gcc/testsuite/gfortran.dg/host_assoc_types_2.f90 index 824a49592173..a3fd3450013b 100644 --- a/gcc/testsuite/gfortran.dg/host_assoc_types_2.f90 +++ b/gcc/testsuite/gfortran.dg/host_assoc_types_2.f90 @@ -66,4 +66,3 @@ contains call overloaded_sub(dval) end subroutine end program -! { dg-final { cleanup-modules "stype dtype" } } diff --git a/gcc/testsuite/gfortran.dg/host_assoc_variable_1.f90 b/gcc/testsuite/gfortran.dg/host_assoc_variable_1.f90 index 1e7adea88949..57231157c181 100644 --- a/gcc/testsuite/gfortran.dg/host_assoc_variable_1.f90 +++ b/gcc/testsuite/gfortran.dg/host_assoc_variable_1.f90 @@ -74,4 +74,3 @@ program testit print *, "in the main:", k call write(33) end program testit -! { dg-final { cleanup-modules "gfcbug68 gfcbug68a m n" } } diff --git a/gcc/testsuite/gfortran.dg/host_used_types_1.f90 b/gcc/testsuite/gfortran.dg/host_used_types_1.f90 index 2076fdb891e2..0dfd9d1ecd98 100644 --- a/gcc/testsuite/gfortran.dg/host_used_types_1.f90 +++ b/gcc/testsuite/gfortran.dg/host_used_types_1.f90 @@ -38,5 +38,3 @@ contains end subroutine SetTimeSteps end module ThermoData - -! { dg-final { cleanup-modules "modelparams thermodata" } } diff --git a/gcc/testsuite/gfortran.dg/implicit_1.f90 b/gcc/testsuite/gfortran.dg/implicit_1.f90 index 21e9d214e3c1..610c473dd8df 100644 --- a/gcc/testsuite/gfortran.dg/implicit_1.f90 +++ b/gcc/testsuite/gfortran.dg/implicit_1.f90 @@ -8,5 +8,3 @@ end module AHFinder_dat implicit none common/rommel/aaa ! { dg-error "no IMPLICIT type" "no IMPLICIT type" } end - -! { dg-final { cleanup-modules "ahfinder_dat" } } diff --git a/gcc/testsuite/gfortran.dg/implicit_10.f90 b/gcc/testsuite/gfortran.dg/implicit_10.f90 index 0f5094f42094..4bb14939173b 100644 --- a/gcc/testsuite/gfortran.dg/implicit_10.f90 +++ b/gcc/testsuite/gfortran.dg/implicit_10.f90 @@ -30,4 +30,3 @@ call sub(di(i),i) if (i.NE.4) call abort() end -! { dg-final { cleanup-modules "mod1" } } diff --git a/gcc/testsuite/gfortran.dg/implicit_11.f90 b/gcc/testsuite/gfortran.dg/implicit_11.f90 index be4ad6ca8c1c..61091ec41a04 100644 --- a/gcc/testsuite/gfortran.dg/implicit_11.f90 +++ b/gcc/testsuite/gfortran.dg/implicit_11.f90 @@ -34,5 +34,3 @@ ALLOCATE (RLA1(NF10), STAT = ISTAT2) ! { dg-error "is not a variable" } END SUBROUTINE END MODULE tests2 - -! { dg-final { cleanup-modules "tests" } } diff --git a/gcc/testsuite/gfortran.dg/implicit_12.f90 b/gcc/testsuite/gfortran.dg/implicit_12.f90 index 3b47352d6cdb..161d4402669d 100644 --- a/gcc/testsuite/gfortran.dg/implicit_12.f90 +++ b/gcc/testsuite/gfortran.dg/implicit_12.f90 @@ -21,5 +21,3 @@ program startest if('#'//Q2//'#' /='#abcdefghijkl#') call abort() call sub('ABCDEFGHIJKLM') ! len=13 end program startest - -! { dg-final { cleanup-modules "mod" } } diff --git a/gcc/testsuite/gfortran.dg/implicit_2.f90 b/gcc/testsuite/gfortran.dg/implicit_2.f90 index 4bff1784000e..c0582d703b60 100644 --- a/gcc/testsuite/gfortran.dg/implicit_2.f90 +++ b/gcc/testsuite/gfortran.dg/implicit_2.f90 @@ -46,5 +46,3 @@ subroutine bar() v%i = 42 end subroutine end module - -! { dg-final { cleanup-modules "implicit_2" } } diff --git a/gcc/testsuite/gfortran.dg/implicit_actual.f90 b/gcc/testsuite/gfortran.dg/implicit_actual.f90 index 750d3f385019..108c04079676 100644 --- a/gcc/testsuite/gfortran.dg/implicit_actual.f90 +++ b/gcc/testsuite/gfortran.dg/implicit_actual.f90 @@ -31,5 +31,3 @@ contains end subroutine foo end program snafu - -! { dg-final { cleanup-modules "global" } } diff --git a/gcc/testsuite/gfortran.dg/implicit_derived_type_1.f90 b/gcc/testsuite/gfortran.dg/implicit_derived_type_1.f90 index 661eb83a5884..baa36d1ba345 100644 --- a/gcc/testsuite/gfortran.dg/implicit_derived_type_1.f90 +++ b/gcc/testsuite/gfortran.dg/implicit_derived_type_1.f90 @@ -18,5 +18,3 @@ contains print *, x(1)%i end subroutine s end module m - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/implicit_pure_1.f90 b/gcc/testsuite/gfortran.dg/implicit_pure_1.f90 index d4a5a364e59b..f49b9ae1938e 100644 --- a/gcc/testsuite/gfortran.dg/implicit_pure_1.f90 +++ b/gcc/testsuite/gfortran.dg/implicit_pure_1.f90 @@ -50,4 +50,3 @@ program gfcbug114a end program gfcbug114a ! { dg-final { scan-module "b" "IMPLICIT_PURE" } } -! { dg-final { cleanup-modules "b" } } diff --git a/gcc/testsuite/gfortran.dg/implicit_pure_2.f90 b/gcc/testsuite/gfortran.dg/implicit_pure_2.f90 index 496e856e04ac..16fa64f39ebe 100644 --- a/gcc/testsuite/gfortran.dg/implicit_pure_2.f90 +++ b/gcc/testsuite/gfortran.dg/implicit_pure_2.f90 @@ -14,4 +14,3 @@ contains end module m ! { dg-final { scan-module-absence "m" "IMPLICIT_PURE" } } -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/import.f90 b/gcc/testsuite/gfortran.dg/import.f90 index 521f87222bef..1934a2c49a7a 100644 --- a/gcc/testsuite/gfortran.dg/import.f90 +++ b/gcc/testsuite/gfortran.dg/import.f90 @@ -75,4 +75,3 @@ program foo call test(z) if(z%i /= 1) call abort() end program foo -! { dg-final { cleanup-modules "testmod" } } diff --git a/gcc/testsuite/gfortran.dg/import2.f90 b/gcc/testsuite/gfortran.dg/import2.f90 index 4a0128a0bf15..d9e65e3cbe0f 100644 --- a/gcc/testsuite/gfortran.dg/import2.f90 +++ b/gcc/testsuite/gfortran.dg/import2.f90 @@ -77,4 +77,3 @@ program foo call test(z) ! { dg-error "Type mismatch in argument" } if(z%i /= 1) call abort() end program foo -! { dg-final { cleanup-modules "testmod" } } diff --git a/gcc/testsuite/gfortran.dg/import4.f90 b/gcc/testsuite/gfortran.dg/import4.f90 index 761c9846b35d..99ffd8ad5a25 100644 --- a/gcc/testsuite/gfortran.dg/import4.f90 +++ b/gcc/testsuite/gfortran.dg/import4.f90 @@ -96,4 +96,3 @@ contains if(r /= -123.0 .or. t%c /= -44) call abort() end subroutine test3 end program all -! { dg-final { cleanup-modules "modtest general" } } diff --git a/gcc/testsuite/gfortran.dg/import5.f90 b/gcc/testsuite/gfortran.dg/import5.f90 index 0106c4ec1214..306ba519a541 100644 --- a/gcc/testsuite/gfortran.dg/import5.f90 +++ b/gcc/testsuite/gfortran.dg/import5.f90 @@ -41,4 +41,3 @@ contains end subroutine sub1 end module test_import -! { dg-final { cleanup-modules "test_import" } } diff --git a/gcc/testsuite/gfortran.dg/import7.f90 b/gcc/testsuite/gfortran.dg/import7.f90 index c115cc3f2b3f..973851fdd7d4 100644 --- a/gcc/testsuite/gfortran.dg/import7.f90 +++ b/gcc/testsuite/gfortran.dg/import7.f90 @@ -53,6 +53,3 @@ END TYPE TYPE(T1) X END - -! { dg-final { cleanup-modules "mod" } } - diff --git a/gcc/testsuite/gfortran.dg/impure_1.f08 b/gcc/testsuite/gfortran.dg/impure_1.f08 index 9d09eaa4c79b..694b6e38b276 100644 --- a/gcc/testsuite/gfortran.dg/impure_1.f08 +++ b/gcc/testsuite/gfortran.dg/impure_1.f08 @@ -67,5 +67,3 @@ CONTAINS END FUNCTION accumulate END PROGRAM main - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/impure_2.f08 b/gcc/testsuite/gfortran.dg/impure_2.f08 index 4bc2ca1fba69..b829e0825a1b 100644 --- a/gcc/testsuite/gfortran.dg/impure_2.f08 +++ b/gcc/testsuite/gfortran.dg/impure_2.f08 @@ -23,5 +23,3 @@ CONTAINS END SUBROUTINE purified END MODULE m - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/impure_actual_1.f90 b/gcc/testsuite/gfortran.dg/impure_actual_1.f90 index 12f3375bf0a5..ee12ddfdacec 100644 --- a/gcc/testsuite/gfortran.dg/impure_actual_1.f90 +++ b/gcc/testsuite/gfortran.dg/impure_actual_1.f90 @@ -20,6 +20,3 @@ END MODULE M1 USE M1 write(6,*) J(L) ! { dg-error "Mismatch in PURE attribute" } END - -! { dg-final { cleanup-modules "m1" } } - diff --git a/gcc/testsuite/gfortran.dg/impure_assignment_1.f90 b/gcc/testsuite/gfortran.dg/impure_assignment_1.f90 index 28ef2693c6df..103244cefa7f 100644 --- a/gcc/testsuite/gfortran.dg/impure_assignment_1.f90 +++ b/gcc/testsuite/gfortran.dg/impure_assignment_1.f90 @@ -24,5 +24,3 @@ PURE SUBROUTINE S2(I,J) I=J ! { dg-error "is not PURE" } END SUBROUTINE S2 END -! { dg-final { cleanup-modules "m1" } } - diff --git a/gcc/testsuite/gfortran.dg/impure_assignment_2.f90 b/gcc/testsuite/gfortran.dg/impure_assignment_2.f90 index 6378ec8a47b3..38d841d7a5d9 100644 --- a/gcc/testsuite/gfortran.dg/impure_assignment_2.f90 +++ b/gcc/testsuite/gfortran.dg/impure_assignment_2.f90 @@ -66,5 +66,3 @@ CONTAINS RES = B END FUNCTION END MODULE pr20882 -! { dg-final { cleanup-modules "pr20863 pr20882" } } - diff --git a/gcc/testsuite/gfortran.dg/impure_constructor_1.f90 b/gcc/testsuite/gfortran.dg/impure_constructor_1.f90 index 01aa01b63a61..cfd99938537f 100644 --- a/gcc/testsuite/gfortran.dg/impure_constructor_1.f90 +++ b/gcc/testsuite/gfortran.dg/impure_constructor_1.f90 @@ -26,5 +26,3 @@ contains z = t3(x) ! { dg-error "Invalid expression in the structure constructor" } end subroutine foo end module m - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/impure_spec_expr_1.f90 b/gcc/testsuite/gfortran.dg/impure_spec_expr_1.f90 index 8c42a57c44ef..1489b5c7398b 100644 --- a/gcc/testsuite/gfortran.dg/impure_spec_expr_1.f90 +++ b/gcc/testsuite/gfortran.dg/impure_spec_expr_1.f90 @@ -11,5 +11,3 @@ contains integer :: u(n(1)) ! { dg-error "must be PURE" } end subroutine end module test -! { dg-final { cleanup-modules "test" } } - diff --git a/gcc/testsuite/gfortran.dg/initialization_1.f90 b/gcc/testsuite/gfortran.dg/initialization_1.f90 index 2fb014ecedd8..ac351e2de248 100644 --- a/gcc/testsuite/gfortran.dg/initialization_1.f90 +++ b/gcc/testsuite/gfortran.dg/initialization_1.f90 @@ -35,5 +35,3 @@ contains end subroutine foo end module const - -! { dg-final { cleanup-modules "const" } } diff --git a/gcc/testsuite/gfortran.dg/initialization_10.f90 b/gcc/testsuite/gfortran.dg/initialization_10.f90 index 387ea6df4930..d8e82d519b82 100644 --- a/gcc/testsuite/gfortran.dg/initialization_10.f90 +++ b/gcc/testsuite/gfortran.dg/initialization_10.f90 @@ -28,5 +28,3 @@ end select END SUBROUTINE Parser END MODULE Readdata_mod - -! { dg-final { cleanup-modules "readdata_mod" } } diff --git a/gcc/testsuite/gfortran.dg/initialization_12.f90 b/gcc/testsuite/gfortran.dg/initialization_12.f90 index 53db60baaf24..1a4812a3729a 100644 --- a/gcc/testsuite/gfortran.dg/initialization_12.f90 +++ b/gcc/testsuite/gfortran.dg/initialization_12.f90 @@ -25,5 +25,3 @@ module AtmoIonoSphere use EGOPS_Utilities use AtmoIono end module AtmoIonoSphere - -! { dg-final { cleanup-modules "egops_utilities atmoiono atmoionosphere" } } diff --git a/gcc/testsuite/gfortran.dg/initialization_19.f90 b/gcc/testsuite/gfortran.dg/initialization_19.f90 index 2465f9b33350..1fba5f01d38f 100644 --- a/gcc/testsuite/gfortran.dg/initialization_19.f90 +++ b/gcc/testsuite/gfortran.dg/initialization_19.f90 @@ -30,5 +30,3 @@ call g call g end program t - -! ! { dg-final { cleanup-modules "c s" } } diff --git a/gcc/testsuite/gfortran.dg/initialization_23.f90 b/gcc/testsuite/gfortran.dg/initialization_23.f90 index cc2aca4e223d..1931bca96b4b 100644 --- a/gcc/testsuite/gfortran.dg/initialization_23.f90 +++ b/gcc/testsuite/gfortran.dg/initialization_23.f90 @@ -12,6 +12,3 @@ CHARACTER, PARAMETER :: the_alpha = one_parameter('c') ! { dg-error "Can't convert TYPE" } CHARACTER, PARAMETER :: the_beta = (/one_parameter('c')/) ! { dg-error "Incompatible ranks" } END MODULE cdf_aux_mod - -! { dg-final { cleanup-modules "cdf_aux_mod" } } - diff --git a/gcc/testsuite/gfortran.dg/inquire_11.f90 b/gcc/testsuite/gfortran.dg/inquire_11.f90 index cc5e26d0908a..f4107661d79c 100644 --- a/gcc/testsuite/gfortran.dg/inquire_11.f90 +++ b/gcc/testsuite/gfortran.dg/inquire_11.f90 @@ -8,4 +8,3 @@ CONTAINS INQUIRE (UNIT=1, EXIST=qexist) END SUBROUTINE i END MODULE print_it -! { dg-final { cleanup-modules "print_it" } } diff --git a/gcc/testsuite/gfortran.dg/int_1.f90 b/gcc/testsuite/gfortran.dg/int_1.f90 index 853578e26921..77ba1e2e69b6 100644 --- a/gcc/testsuite/gfortran.dg/int_1.f90 +++ b/gcc/testsuite/gfortran.dg/int_1.f90 @@ -171,5 +171,3 @@ program test_int if (i4 /= 17_ik4 .or. i8 /= 17_ik8) call abort end program test_int - -! { dg-final { cleanup-modules "mykinds" } } diff --git a/gcc/testsuite/gfortran.dg/int_2.f90 b/gcc/testsuite/gfortran.dg/int_2.f90 index b9a3ec43d4cf..a6006aad8f0d 100644 --- a/gcc/testsuite/gfortran.dg/int_2.f90 +++ b/gcc/testsuite/gfortran.dg/int_2.f90 @@ -1,6 +1,5 @@ ! PR fortran/32823 ! { dg-do compile } -! { dg-final { cleanup-modules "token_module" } } module token_module diff --git a/gcc/testsuite/gfortran.dg/integer_exponentiation_3.F90 b/gcc/testsuite/gfortran.dg/integer_exponentiation_3.F90 index 5c6c5bfe5e6b..e4088c361aaa 100644 --- a/gcc/testsuite/gfortran.dg/integer_exponentiation_3.F90 +++ b/gcc/testsuite/gfortran.dg/integer_exponentiation_3.F90 @@ -201,5 +201,3 @@ program test ATEST((1.0,0.),-9,c4) end program test - -! { dg-final { cleanup-modules "mod_check" } } diff --git a/gcc/testsuite/gfortran.dg/integer_exponentiation_5.F90 b/gcc/testsuite/gfortran.dg/integer_exponentiation_5.F90 index 58c7614d514e..35bb28167846 100644 --- a/gcc/testsuite/gfortran.dg/integer_exponentiation_5.F90 +++ b/gcc/testsuite/gfortran.dg/integer_exponentiation_5.F90 @@ -76,5 +76,3 @@ program test TEST(nearest(1.0,-1.0),-huge(0),r4) end program test - -! { dg-final { cleanup-modules "mod_check" } } diff --git a/gcc/testsuite/gfortran.dg/intent_out_2.f90 b/gcc/testsuite/gfortran.dg/intent_out_2.f90 index 4dc5191e9a21..e85cf84f3a10 100644 --- a/gcc/testsuite/gfortran.dg/intent_out_2.f90 +++ b/gcc/testsuite/gfortran.dg/intent_out_2.f90 @@ -43,5 +43,3 @@ program test implicit none call setup () end program test -! { dg-final { cleanup-modules "gfcbug72" } } - diff --git a/gcc/testsuite/gfortran.dg/intent_out_3.f90 b/gcc/testsuite/gfortran.dg/intent_out_3.f90 index e3300c988f50..1afb504be06f 100644 --- a/gcc/testsuite/gfortran.dg/intent_out_3.f90 +++ b/gcc/testsuite/gfortran.dg/intent_out_3.f90 @@ -17,4 +17,3 @@ END MODULE M1 USE M1 CALL S1(D1%I(3)) ! { dg-error "variable definition context" } END -! { dg-final { cleanup-modules "m1" } } diff --git a/gcc/testsuite/gfortran.dg/intent_out_6.f90 b/gcc/testsuite/gfortran.dg/intent_out_6.f90 index 1a411072faa8..a36316428fa0 100644 --- a/gcc/testsuite/gfortran.dg/intent_out_6.f90 +++ b/gcc/testsuite/gfortran.dg/intent_out_6.f90 @@ -35,5 +35,3 @@ program test call sub1(x) if(x(1) /= 5) call abort() end program - -! { dg-final { cleanup-modules "test_module" } } diff --git a/gcc/testsuite/gfortran.dg/intent_used_1.f90 b/gcc/testsuite/gfortran.dg/intent_used_1.f90 index ec23bf585799..ecc06e989cea 100644 --- a/gcc/testsuite/gfortran.dg/intent_used_1.f90 +++ b/gcc/testsuite/gfortran.dg/intent_used_1.f90 @@ -15,5 +15,3 @@ MODULE global END SUBROUTINE foo END INTERFACE END MODULE global - -! { dg-final { cleanup-modules "global" } } diff --git a/gcc/testsuite/gfortran.dg/interface_1.f90 b/gcc/testsuite/gfortran.dg/interface_1.f90 index e170f870e1a4..3bbdd570c0fa 100644 --- a/gcc/testsuite/gfortran.dg/interface_1.f90 +++ b/gcc/testsuite/gfortran.dg/interface_1.f90 @@ -38,5 +38,3 @@ module z end function end module z - -! { dg-final { cleanup-modules "y z" } } diff --git a/gcc/testsuite/gfortran.dg/interface_10.f90 b/gcc/testsuite/gfortran.dg/interface_10.f90 index 99ecc8c857df..96c364b57978 100644 --- a/gcc/testsuite/gfortran.dg/interface_10.f90 +++ b/gcc/testsuite/gfortran.dg/interface_10.f90 @@ -54,4 +54,3 @@ contains nsz=size(x) end subroutine solve_s_foo end module class_s_foo -! { dg-final { cleanup-modules "class_s_fld class_fld class_s_foo" } } diff --git a/gcc/testsuite/gfortran.dg/interface_11.f90 b/gcc/testsuite/gfortran.dg/interface_11.f90 index a143bb374f2c..9a7e7809079c 100644 --- a/gcc/testsuite/gfortran.dg/interface_11.f90 +++ b/gcc/testsuite/gfortran.dg/interface_11.f90 @@ -26,4 +26,3 @@ CONTAINS END MODULE END -! { dg-final { cleanup-modules "m1" } } diff --git a/gcc/testsuite/gfortran.dg/interface_12.f90 b/gcc/testsuite/gfortran.dg/interface_12.f90 index a45817dabb89..d519789bf93b 100644 --- a/gcc/testsuite/gfortran.dg/interface_12.f90 +++ b/gcc/testsuite/gfortran.dg/interface_12.f90 @@ -87,4 +87,3 @@ pure function f (x) f = 2*x+1 end function f -! { dg-final { cleanup-modules "test1" } } diff --git a/gcc/testsuite/gfortran.dg/interface_13.f90 b/gcc/testsuite/gfortran.dg/interface_13.f90 index 42c794a3e513..a29342553cdc 100644 --- a/gcc/testsuite/gfortran.dg/interface_13.f90 +++ b/gcc/testsuite/gfortran.dg/interface_13.f90 @@ -29,5 +29,3 @@ data_r8(1)=0 end subroutine my_sio_file_read_common end module files_module - -! { dg-final { cleanup-modules "files_module" } } diff --git a/gcc/testsuite/gfortran.dg/interface_14.f90 b/gcc/testsuite/gfortran.dg/interface_14.f90 index 994d97ee737b..ebd16f9a78cd 100644 --- a/gcc/testsuite/gfortran.dg/interface_14.f90 +++ b/gcc/testsuite/gfortran.dg/interface_14.f90 @@ -69,5 +69,3 @@ call new (a) call new (b) end - -! { dg-final { cleanup-modules "p_class s_class t_class d_class poly_class" } } diff --git a/gcc/testsuite/gfortran.dg/interface_15.f90 b/gcc/testsuite/gfortran.dg/interface_15.f90 index 8ad940ae77be..49aaddace83c 100644 --- a/gcc/testsuite/gfortran.dg/interface_15.f90 +++ b/gcc/testsuite/gfortran.dg/interface_15.f90 @@ -18,5 +18,3 @@ CONTAINS F1 = D%I END FUNCTION END MODULE - -! { dg-final { cleanup-modules "m1" } } diff --git a/gcc/testsuite/gfortran.dg/interface_16.f90 b/gcc/testsuite/gfortran.dg/interface_16.f90 index 8be9d684a662..1cad75f3c43e 100644 --- a/gcc/testsuite/gfortran.dg/interface_16.f90 +++ b/gcc/testsuite/gfortran.dg/interface_16.f90 @@ -96,6 +96,3 @@ Subroutine foo_sub(a,pr,b,x,eps,cd,info) Call foo_pwrk(pr,p,f,cd,info,work=aux) ! This worked if bar_pwrk was called! return End Subroutine foo_sub - -! { dg-final { cleanup-modules "foo_base_mod foo_pr_mod bar_pr_mod bar_prt" } } - diff --git a/gcc/testsuite/gfortran.dg/interface_17.f90 b/gcc/testsuite/gfortran.dg/interface_17.f90 index 44b8a4615972..9315137543d6 100644 --- a/gcc/testsuite/gfortran.dg/interface_17.f90 +++ b/gcc/testsuite/gfortran.dg/interface_17.f90 @@ -21,4 +21,3 @@ END MODULE util MODULE graphcon USE util, ONLY: sort END MODULE graphcon -! { dg-final { cleanup-modules "kinds util graphcon" } } diff --git a/gcc/testsuite/gfortran.dg/interface_18.f90 b/gcc/testsuite/gfortran.dg/interface_18.f90 index d0a54754883b..30461e5c4c78 100644 --- a/gcc/testsuite/gfortran.dg/interface_18.f90 +++ b/gcc/testsuite/gfortran.dg/interface_18.f90 @@ -17,5 +17,3 @@ type(mytype_type), intent(in out) :: mytype end subroutine mytype_test end module mytype_application - -! { dg-final { cleanup-modules "mytype_application" } } diff --git a/gcc/testsuite/gfortran.dg/interface_19.f90 b/gcc/testsuite/gfortran.dg/interface_19.f90 index 7a88fc91b3ef..2d72caa058d6 100644 --- a/gcc/testsuite/gfortran.dg/interface_19.f90 +++ b/gcc/testsuite/gfortran.dg/interface_19.f90 @@ -27,6 +27,3 @@ intrinsic dcos call sub() call sub(dcos) end - -! { dg-final { cleanup-modules "m" } } - diff --git a/gcc/testsuite/gfortran.dg/interface_2.f90 b/gcc/testsuite/gfortran.dg/interface_2.f90 index 4e6309899e47..6b0bf2b239bb 100644 --- a/gcc/testsuite/gfortran.dg/interface_2.f90 +++ b/gcc/testsuite/gfortran.dg/interface_2.f90 @@ -27,5 +27,3 @@ CONTAINS END FUNCTION Compare_Float_Single END MODULE Compare_Float_Numbers - -! { dg-final { cleanup-modules "compare_float_numbers" } } diff --git a/gcc/testsuite/gfortran.dg/interface_20.f90 b/gcc/testsuite/gfortran.dg/interface_20.f90 index 9a7dc5cb1315..829add2ff9b0 100644 --- a/gcc/testsuite/gfortran.dg/interface_20.f90 +++ b/gcc/testsuite/gfortran.dg/interface_20.f90 @@ -18,6 +18,3 @@ implicit none intrinsic cos call sub(cos) ! { dg-error "wrong number of arguments" } end - -! { dg-final { cleanup-modules "m" } } - diff --git a/gcc/testsuite/gfortran.dg/interface_21.f90 b/gcc/testsuite/gfortran.dg/interface_21.f90 index 566a9ef37075..e3db771a93d4 100644 --- a/gcc/testsuite/gfortran.dg/interface_21.f90 +++ b/gcc/testsuite/gfortran.dg/interface_21.f90 @@ -20,6 +20,3 @@ implicit none EXTERNAL foo ! implicit interface is undefined call sub(foo) ! { dg-error "is not a function" } end - -! { dg-final { cleanup-modules "m" } } - diff --git a/gcc/testsuite/gfortran.dg/interface_22.f90 b/gcc/testsuite/gfortran.dg/interface_22.f90 index fa8e517a1865..6228fc9f1336 100644 --- a/gcc/testsuite/gfortran.dg/interface_22.f90 +++ b/gcc/testsuite/gfortran.dg/interface_22.f90 @@ -23,6 +23,3 @@ module gswap module procedure sreal, schar, sint => sreal ! { dg-error "Syntax error in MODULE PROCEDURE statement" } end interface swap end module gswap - -! { dg-final { cleanup-modules "foo g gswap" } } - diff --git a/gcc/testsuite/gfortran.dg/interface_23.f90 b/gcc/testsuite/gfortran.dg/interface_23.f90 index 60b6e7969088..b2e7a697fd22 100644 --- a/gcc/testsuite/gfortran.dg/interface_23.f90 +++ b/gcc/testsuite/gfortran.dg/interface_23.f90 @@ -31,5 +31,3 @@ program c end interface call bar() ! { dg-error "Missing actual argument" } end program - -! { dg-final { cleanup-modules "a b" } } diff --git a/gcc/testsuite/gfortran.dg/interface_24.f90 b/gcc/testsuite/gfortran.dg/interface_24.f90 index 1afc5ef2fbac..f97d2babcdb9 100644 --- a/gcc/testsuite/gfortran.dg/interface_24.f90 +++ b/gcc/testsuite/gfortran.dg/interface_24.f90 @@ -62,5 +62,3 @@ module m6 end function end interface end module - -! { dg-final { cleanup-modules "m1 m2 m3 m4 m5 m6" } } diff --git a/gcc/testsuite/gfortran.dg/interface_25.f90 b/gcc/testsuite/gfortran.dg/interface_25.f90 index b239b2125a78..0118cd563c73 100644 --- a/gcc/testsuite/gfortran.dg/interface_25.f90 +++ b/gcc/testsuite/gfortran.dg/interface_25.f90 @@ -43,5 +43,3 @@ CONTAINS end if END FUNCTION recSum END PROGRAM test - -! { dg-final { cleanup-modules "funcs" } } diff --git a/gcc/testsuite/gfortran.dg/interface_26.f90 b/gcc/testsuite/gfortran.dg/interface_26.f90 index 54ede6d53eb3..52e0bd138b90 100644 --- a/gcc/testsuite/gfortran.dg/interface_26.f90 +++ b/gcc/testsuite/gfortran.dg/interface_26.f90 @@ -44,5 +44,3 @@ CONTAINS end if END FUNCTION recSum END PROGRAM test - -! { dg-final { cleanup-modules "funcs" } } diff --git a/gcc/testsuite/gfortran.dg/interface_27.f90 b/gcc/testsuite/gfortran.dg/interface_27.f90 index 71975b6b7d29..128d6a6f52af 100644 --- a/gcc/testsuite/gfortran.dg/interface_27.f90 +++ b/gcc/testsuite/gfortran.dg/interface_27.f90 @@ -36,6 +36,3 @@ subroutine caller end subroutine end module - -! { dg-final { cleanup-modules "m" } } - diff --git a/gcc/testsuite/gfortran.dg/interface_28.f90 b/gcc/testsuite/gfortran.dg/interface_28.f90 index 42a8208f4b34..c82722708367 100644 --- a/gcc/testsuite/gfortran.dg/interface_28.f90 +++ b/gcc/testsuite/gfortran.dg/interface_28.f90 @@ -38,6 +38,3 @@ program interfaceCheck call test(subActual) ! { dg-error "INTENT mismatch in argument" } call test(subActual2) ! { dg-error "OPTIONAL mismatch in argument" } end program - -! { dg-final { cleanup-modules "sub testsub" } } - diff --git a/gcc/testsuite/gfortran.dg/interface_29.f90 b/gcc/testsuite/gfortran.dg/interface_29.f90 index b3d123a42b16..4a5626d0034c 100644 --- a/gcc/testsuite/gfortran.dg/interface_29.f90 +++ b/gcc/testsuite/gfortran.dg/interface_29.f90 @@ -47,6 +47,3 @@ end subroutine bar complex, intent(out) :: y(:) end subroutine end module test - -! { dg-final { cleanup-modules "m test" } } - diff --git a/gcc/testsuite/gfortran.dg/interface_3.f90 b/gcc/testsuite/gfortran.dg/interface_3.f90 index 1d954eef8b6d..febb12050db7 100644 --- a/gcc/testsuite/gfortran.dg/interface_3.f90 +++ b/gcc/testsuite/gfortran.dg/interface_3.f90 @@ -67,5 +67,3 @@ subroutine his_fun (a) use test_mod2 print *, my_fun (a) ! { dg-error "ambiguous reference" } end subroutine his_fun - -! { dg-final { cleanup-modules "test_mod test_mod2" } } diff --git a/gcc/testsuite/gfortran.dg/interface_31.f90 b/gcc/testsuite/gfortran.dg/interface_31.f90 index 3b0e8f8283bf..88aac32c2e7d 100644 --- a/gcc/testsuite/gfortran.dg/interface_31.f90 +++ b/gcc/testsuite/gfortran.dg/interface_31.f90 @@ -38,4 +38,3 @@ CONTAINS r%j = lhs%j + rhs%j END FUNCTION add_b END MODULE mod2 -! { dg-final { cleanup-modules "mod1 mod2" } } diff --git a/gcc/testsuite/gfortran.dg/interface_32.f90 b/gcc/testsuite/gfortran.dg/interface_32.f90 index 6cdb091aecc7..a0f5f15d4a44 100644 --- a/gcc/testsuite/gfortran.dg/interface_32.f90 +++ b/gcc/testsuite/gfortran.dg/interface_32.f90 @@ -78,4 +78,3 @@ contains ip_save => g_initial%inquire_inner_product() end subroutine cg end module m4 -! { dg-final { cleanup-modules "m1 m2 m3 m4" } } diff --git a/gcc/testsuite/gfortran.dg/interface_33.f90 b/gcc/testsuite/gfortran.dg/interface_33.f90 index 955d50731bc7..60543f9d5c92 100644 --- a/gcc/testsuite/gfortran.dg/interface_33.f90 +++ b/gcc/testsuite/gfortran.dg/interface_33.f90 @@ -32,5 +32,3 @@ CONTAINS SUBROUTINE subr_name() END SUBROUTINE END MODULE - -! { dg-final { cleanup-modules "m1 m2" } } diff --git a/gcc/testsuite/gfortran.dg/interface_35.f90 b/gcc/testsuite/gfortran.dg/interface_35.f90 index eb4de12c1bd3..8c62a5dbb601 100644 --- a/gcc/testsuite/gfortran.dg/interface_35.f90 +++ b/gcc/testsuite/gfortran.dg/interface_35.f90 @@ -75,5 +75,3 @@ contains end function end - -! { dg-final { cleanup-modules "module_m module_m2 s_hard sidl_string_array" } } diff --git a/gcc/testsuite/gfortran.dg/interface_4.f90 b/gcc/testsuite/gfortran.dg/interface_4.f90 index 8f6c3317eefa..a09d656f91c5 100644 --- a/gcc/testsuite/gfortran.dg/interface_4.f90 +++ b/gcc/testsuite/gfortran.dg/interface_4.f90 @@ -43,4 +43,3 @@ program main call bl_copy(1.0, chr) if (chr /= "recopy") call abort () end program main -! { dg-final { cleanup-modules "f77_blas_generic f77_blas_extra" } } diff --git a/gcc/testsuite/gfortran.dg/interface_5.f90 b/gcc/testsuite/gfortran.dg/interface_5.f90 index cc5a7129d4ec..de7719178ca8 100644 --- a/gcc/testsuite/gfortran.dg/interface_5.f90 +++ b/gcc/testsuite/gfortran.dg/interface_5.f90 @@ -53,4 +53,3 @@ program main call bl_copy(1.0, chr) if (chr /= "recopy") call abort () end program main -! { dg-final { cleanup-modules "f77_blas_generic f77_blas_extra" } } diff --git a/gcc/testsuite/gfortran.dg/interface_7.f90 b/gcc/testsuite/gfortran.dg/interface_7.f90 index 9f59b4972146..b3274ef9b83e 100644 --- a/gcc/testsuite/gfortran.dg/interface_7.f90 +++ b/gcc/testsuite/gfortran.dg/interface_7.f90 @@ -28,5 +28,3 @@ module xx END SUBROUTINE S9C ! { dg-error "Ambiguous interfaces" } END INTERFACE BAD9 end module xx - -! { dg-final { cleanup-modules "xx" } } diff --git a/gcc/testsuite/gfortran.dg/interface_8.f90 b/gcc/testsuite/gfortran.dg/interface_8.f90 index 7feccb38b407..2060e7dd66d3 100644 --- a/gcc/testsuite/gfortran.dg/interface_8.f90 +++ b/gcc/testsuite/gfortran.dg/interface_8.f90 @@ -26,5 +26,3 @@ program main use mod1, only: generic ! { dg-warning "has ambiguous interfaces" } use mod2 end program main - -! { dg-final { cleanup-modules "mod1 mod2" } } diff --git a/gcc/testsuite/gfortran.dg/interface_9.f90 b/gcc/testsuite/gfortran.dg/interface_9.f90 index b407ab065240..2f38040b933a 100644 --- a/gcc/testsuite/gfortran.dg/interface_9.f90 +++ b/gcc/testsuite/gfortran.dg/interface_9.f90 @@ -42,6 +42,3 @@ contains if (inverse(1_4) /= 3_4) call abort () end subroutine sub end program gfcbug48 - -! { dg-final { cleanup-modules "module1 module2" } } - diff --git a/gcc/testsuite/gfortran.dg/interface_assignment_1.f90 b/gcc/testsuite/gfortran.dg/interface_assignment_1.f90 index 51298328506f..f76b9da496de 100644 --- a/gcc/testsuite/gfortran.dg/interface_assignment_1.f90 +++ b/gcc/testsuite/gfortran.dg/interface_assignment_1.f90 @@ -36,4 +36,3 @@ CALL set(E,(E)) IF (D%I.NE.4) call abort () IF (4.NE.E%I) call abort () END -! { dg-final { cleanup-modules "tt" } } diff --git a/gcc/testsuite/gfortran.dg/interface_assignment_2.f90 b/gcc/testsuite/gfortran.dg/interface_assignment_2.f90 index 8d7484b31bf6..e17d78e5a7d6 100644 --- a/gcc/testsuite/gfortran.dg/interface_assignment_2.f90 +++ b/gcc/testsuite/gfortran.dg/interface_assignment_2.f90 @@ -46,4 +46,3 @@ PROGRAM VST_2 if (any (str_ara(1)%chars(1:5) .ne. char_elm(1:5))) call abort if (any (str_ara(2)%chars(1:5) .ne. char_elm(6:10))) call abort END PROGRAM VST_2 -! { dg-final { cleanup-modules "iso_varying_string" } } diff --git a/gcc/testsuite/gfortran.dg/interface_assignment_3.f90 b/gcc/testsuite/gfortran.dg/interface_assignment_3.f90 index 6b7881bd143a..2f5c7ae83e08 100644 --- a/gcc/testsuite/gfortran.dg/interface_assignment_3.f90 +++ b/gcc/testsuite/gfortran.dg/interface_assignment_3.f90 @@ -45,5 +45,3 @@ contains y% m = x% m ! ICE end subroutine assign_atm_to_atm end module gfcbug74 -! { dg-final { cleanup-modules "mo_memory gfcbug74" } } - diff --git a/gcc/testsuite/gfortran.dg/interface_assignment_5.f90 b/gcc/testsuite/gfortran.dg/interface_assignment_5.f90 index 8444dd0847eb..ac834bbf6bf1 100644 --- a/gcc/testsuite/gfortran.dg/interface_assignment_5.f90 +++ b/gcc/testsuite/gfortran.dg/interface_assignment_5.f90 @@ -46,4 +46,3 @@ contains end subroutine assign_to_atm end module mod2 -! { dg-final { cleanup-modules "mod1 mod2" } } diff --git a/gcc/testsuite/gfortran.dg/interface_derived_type_1.f90 b/gcc/testsuite/gfortran.dg/interface_derived_type_1.f90 index a2c4d02bee38..7c165b336e9c 100644 --- a/gcc/testsuite/gfortran.dg/interface_derived_type_1.f90 +++ b/gcc/testsuite/gfortran.dg/interface_derived_type_1.f90 @@ -52,5 +52,3 @@ subroutine sim_3(func3,params) end interface type(fcnparms) :: params ! -ditto- end subroutine sim_3 - -! { dg-final { cleanup-modules "test type_decl" } } diff --git a/gcc/testsuite/gfortran.dg/interface_proc_end.f90 b/gcc/testsuite/gfortran.dg/interface_proc_end.f90 index efe5855584a8..2fc9921df413 100644 --- a/gcc/testsuite/gfortran.dg/interface_proc_end.f90 +++ b/gcc/testsuite/gfortran.dg/interface_proc_end.f90 @@ -16,5 +16,3 @@ END INTERFACE end subroutine end module - -! { dg-final { cleanup-modules "n" } } diff --git a/gcc/testsuite/gfortran.dg/internal_dummy_2.f08 b/gcc/testsuite/gfortran.dg/internal_dummy_2.f08 index 7ec6ad4c6484..2d2ec6837b71 100644 --- a/gcc/testsuite/gfortran.dg/internal_dummy_2.f08 +++ b/gcc/testsuite/gfortran.dg/internal_dummy_2.f08 @@ -60,5 +60,3 @@ CONTAINS END SUBROUTINE incA END PROGRAM main - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/internal_dummy_3.f08 b/gcc/testsuite/gfortran.dg/internal_dummy_3.f08 index 9780c27b3b44..ff8dd822ec3d 100644 --- a/gcc/testsuite/gfortran.dg/internal_dummy_3.f08 +++ b/gcc/testsuite/gfortran.dg/internal_dummy_3.f08 @@ -62,5 +62,3 @@ PROGRAM main CALL test (1) END PROGRAM main - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/internal_dummy_4.f08 b/gcc/testsuite/gfortran.dg/internal_dummy_4.f08 index 1d8b8b2288e0..8ade99efb88f 100644 --- a/gcc/testsuite/gfortran.dg/internal_dummy_4.f08 +++ b/gcc/testsuite/gfortran.dg/internal_dummy_4.f08 @@ -54,4 +54,3 @@ contains two = -123*y end function two end program main -! { dg-final { cleanup-modules "test_mod" } } diff --git a/gcc/testsuite/gfortran.dg/internal_pack_10.f90 b/gcc/testsuite/gfortran.dg/internal_pack_10.f90 index 8d972f44c181..fd1574dbfa9e 100644 --- a/gcc/testsuite/gfortran.dg/internal_pack_10.f90 +++ b/gcc/testsuite/gfortran.dg/internal_pack_10.f90 @@ -38,4 +38,3 @@ program test type(t_set) :: c (1) call get_rule (c) end program test -! { dg-final { cleanup-modules "mo_obs_rules" } } diff --git a/gcc/testsuite/gfortran.dg/internal_pack_12.f90 b/gcc/testsuite/gfortran.dg/internal_pack_12.f90 index 32bacfa39302..bdcc7d109086 100644 --- a/gcc/testsuite/gfortran.dg/internal_pack_12.f90 +++ b/gcc/testsuite/gfortran.dg/internal_pack_12.f90 @@ -57,5 +57,3 @@ subroutine bar(x) end subroutine bar ! { dg-final { scan-tree-dump-times "unpack" 4 "original" } } ! { dg-final { cleanup-tree-dump "original" } } -! { dg-final { cleanup-modules "m" } } - diff --git a/gcc/testsuite/gfortran.dg/internal_pack_4.f90 b/gcc/testsuite/gfortran.dg/internal_pack_4.f90 index 5ddc035e9c48..0bcfc799a8e4 100644 --- a/gcc/testsuite/gfortran.dg/internal_pack_4.f90 +++ b/gcc/testsuite/gfortran.dg/internal_pack_4.f90 @@ -29,4 +29,3 @@ END ! { dg-final { scan-tree-dump-times "a != 0B \\? \\\(.*\\\) _gfortran_internal_pack" 1 "original" } } ! { dg-final { scan-tree-dump-times "if \\(a != 0B &&" 1 "original" } } ! { dg-final { cleanup-tree-dump "original" } } -! { dg-final { cleanup-modules "m1" } } diff --git a/gcc/testsuite/gfortran.dg/internal_pack_6.f90 b/gcc/testsuite/gfortran.dg/internal_pack_6.f90 index 05dd20aee8f2..7ec322575923 100644 --- a/gcc/testsuite/gfortran.dg/internal_pack_6.f90 +++ b/gcc/testsuite/gfortran.dg/internal_pack_6.f90 @@ -54,6 +54,5 @@ END SUBROUTINE S2 call s2 end -! { dg-final { cleanup-modules "m1" } } ! { dg-final { scan-tree-dump-times "_gfortran_internal_pack" 0 "original" } } ! { dg-final { cleanup-tree-dump "original" } } diff --git a/gcc/testsuite/gfortran.dg/internal_pack_7.f90 b/gcc/testsuite/gfortran.dg/internal_pack_7.f90 index 32d98f77250c..2a056fcb90c9 100644 --- a/gcc/testsuite/gfortran.dg/internal_pack_7.f90 +++ b/gcc/testsuite/gfortran.dg/internal_pack_7.f90 @@ -30,6 +30,5 @@ CONTAINS s2=0 END FUNCTION S2 END MODULE M1 -! { dg-final { cleanup-modules "m1" } } ! { dg-final { scan-tree-dump-times "pack" 0 "original" } } ! { dg-final { cleanup-tree-dump "original" } } diff --git a/gcc/testsuite/gfortran.dg/internal_pack_8.f90 b/gcc/testsuite/gfortran.dg/internal_pack_8.f90 index d38403fa4abf..0e27aab7652f 100644 --- a/gcc/testsuite/gfortran.dg/internal_pack_8.f90 +++ b/gcc/testsuite/gfortran.dg/internal_pack_8.f90 @@ -30,4 +30,3 @@ END MODULE M1 USE M1 CALL S1 END -! { dg-final { cleanup-modules "m1" } } diff --git a/gcc/testsuite/gfortran.dg/internal_references_1.f90 b/gcc/testsuite/gfortran.dg/internal_references_1.f90 index 73b9da67c648..12041df9d704 100644 --- a/gcc/testsuite/gfortran.dg/internal_references_1.f90 +++ b/gcc/testsuite/gfortran.dg/internal_references_1.f90 @@ -33,4 +33,3 @@ contains bar = 1.0 end function bar end program test -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/internal_references_2.f90 b/gcc/testsuite/gfortran.dg/internal_references_2.f90 index 6d4c21dc2181..d72d9065adb8 100644 --- a/gcc/testsuite/gfortran.dg/internal_references_2.f90 +++ b/gcc/testsuite/gfortran.dg/internal_references_2.f90 @@ -18,5 +18,3 @@ contains real a end subroutine sub end module aap - -! { dg-final { cleanup-modules "aap" } } diff --git a/gcc/testsuite/gfortran.dg/intrinsic_1.f90 b/gcc/testsuite/gfortran.dg/intrinsic_1.f90 index b2413de1a3f8..15c0d39ac17e 100644 --- a/gcc/testsuite/gfortran.dg/intrinsic_1.f90 +++ b/gcc/testsuite/gfortran.dg/intrinsic_1.f90 @@ -23,6 +23,3 @@ contains END FUNCTION next_state end module vector_calculus - -! { dg-final { cleanup-modules "vector_calculus" } } - diff --git a/gcc/testsuite/gfortran.dg/intrinsic_3.f90 b/gcc/testsuite/gfortran.dg/intrinsic_3.f90 index fcd40e94bbb2..3d639e3744ea 100644 --- a/gcc/testsuite/gfortran.dg/intrinsic_3.f90 +++ b/gcc/testsuite/gfortran.dg/intrinsic_3.f90 @@ -35,6 +35,3 @@ module p end function erfc end module p - -! { dg-final { cleanup-modules "p" } } - diff --git a/gcc/testsuite/gfortran.dg/intrinsic_shadow_1.f03 b/gcc/testsuite/gfortran.dg/intrinsic_shadow_1.f03 index 776d0f692d9e..8ad3a6379ab2 100644 --- a/gcc/testsuite/gfortran.dg/intrinsic_shadow_1.f03 +++ b/gcc/testsuite/gfortran.dg/intrinsic_shadow_1.f03 @@ -53,5 +53,3 @@ REAL FUNCTION random_seed () ! { dg-bogus "of an intrinsic" } END FUNCTION random_seed ! We do only compile, so no main program needed. - -! { dg-final { cleanup-modules "testmod" } } diff --git a/gcc/testsuite/gfortran.dg/intrinsic_shadow_2.f03 b/gcc/testsuite/gfortran.dg/intrinsic_shadow_2.f03 index 5c046166d76b..326edb0c5736 100644 --- a/gcc/testsuite/gfortran.dg/intrinsic_shadow_2.f03 +++ b/gcc/testsuite/gfortran.dg/intrinsic_shadow_2.f03 @@ -25,5 +25,3 @@ REAL FUNCTION acosh (arg) ! { dg-warning "of an intrinsic" } END FUNCTION acosh ! We do only compile, so no main program needed. - -! { dg-final { cleanup-modules "testmod" } } diff --git a/gcc/testsuite/gfortran.dg/intrinsic_shadow_3.f03 b/gcc/testsuite/gfortran.dg/intrinsic_shadow_3.f03 index 069a99b34335..4516349a6423 100644 --- a/gcc/testsuite/gfortran.dg/intrinsic_shadow_3.f03 +++ b/gcc/testsuite/gfortran.dg/intrinsic_shadow_3.f03 @@ -23,5 +23,3 @@ REAL FUNCTION acos (arg) ! { dg-bogus "of an intrinsic" } END FUNCTION acos ! We do only compile, so no main program needed. - -! { dg-final { cleanup-modules "testmod" } } diff --git a/gcc/testsuite/gfortran.dg/io_constraints_1.f90 b/gcc/testsuite/gfortran.dg/io_constraints_1.f90 index eb8ab8d5349a..c6f956958c7e 100644 --- a/gcc/testsuite/gfortran.dg/io_constraints_1.f90 +++ b/gcc/testsuite/gfortran.dg/io_constraints_1.f90 @@ -76,5 +76,3 @@ end module global 100 continue 200 format (2i6) END - -! { dg-final { cleanup-modules "fails global" } } diff --git a/gcc/testsuite/gfortran.dg/io_constraints_2.f90 b/gcc/testsuite/gfortran.dg/io_constraints_2.f90 index 42aba66a8d52..e0e0db633243 100644 --- a/gcc/testsuite/gfortran.dg/io_constraints_2.f90 +++ b/gcc/testsuite/gfortran.dg/io_constraints_2.f90 @@ -73,5 +73,3 @@ end module global 100 continue 200 format (2i6) END - -! { dg-final { cleanup-modules "global" } } diff --git a/gcc/testsuite/gfortran.dg/io_constraints_6.f03 b/gcc/testsuite/gfortran.dg/io_constraints_6.f03 index d0484f5f4fe1..be7b1c45b393 100644 --- a/gcc/testsuite/gfortran.dg/io_constraints_6.f03 +++ b/gcc/testsuite/gfortran.dg/io_constraints_6.f03 @@ -36,5 +36,3 @@ program main read (*, nml=definable) write (*, nml=definable) end program main - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/io_constraints_7.f03 b/gcc/testsuite/gfortran.dg/io_constraints_7.f03 index 4d1849198148..6b686f38d2b6 100644 --- a/gcc/testsuite/gfortran.dg/io_constraints_7.f03 +++ b/gcc/testsuite/gfortran.dg/io_constraints_7.f03 @@ -33,5 +33,3 @@ program main open (newunit=a, file="foo") ! { dg-error "variable definition context" } close (unit=a) end program main - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/iso_c_binding_compiler_3.f90 b/gcc/testsuite/gfortran.dg/iso_c_binding_compiler_3.f90 index d9f9dfdd7912..71fde9db68f5 100644 --- a/gcc/testsuite/gfortran.dg/iso_c_binding_compiler_3.f90 +++ b/gcc/testsuite/gfortran.dg/iso_c_binding_compiler_3.f90 @@ -23,5 +23,3 @@ end module test_mod subroutine test use test_mod end subroutine test - -! { dg-final { cleanup-modules "test_mod" } } diff --git a/gcc/testsuite/gfortran.dg/iso_c_binding_compiler_4.f90 b/gcc/testsuite/gfortran.dg/iso_c_binding_compiler_4.f90 index 8a87fe5f50c8..4c35264d9310 100644 --- a/gcc/testsuite/gfortran.dg/iso_c_binding_compiler_4.f90 +++ b/gcc/testsuite/gfortran.dg/iso_c_binding_compiler_4.f90 @@ -14,5 +14,3 @@ module mymod public :: c_null_ptr end module mymod - -! { dg-final { cleanup-modules "mymod" } } diff --git a/gcc/testsuite/gfortran.dg/iso_c_binding_only.f03 b/gcc/testsuite/gfortran.dg/iso_c_binding_only.f03 index dff4318e806a..be2fbbf43f60 100644 --- a/gcc/testsuite/gfortran.dg/iso_c_binding_only.f03 +++ b/gcc/testsuite/gfortran.dg/iso_c_binding_only.f03 @@ -7,5 +7,3 @@ module iso_c_binding_only ! a mangled name to prevent collisions. integer :: c_ptr end module iso_c_binding_only -! { dg-final { cleanup-modules "iso_c_binding_only" } } - diff --git a/gcc/testsuite/gfortran.dg/iso_c_binding_rename_1.f03 b/gcc/testsuite/gfortran.dg/iso_c_binding_rename_1.f03 index 799ba35e9bc4..12828a7f545a 100644 --- a/gcc/testsuite/gfortran.dg/iso_c_binding_rename_1.f03 +++ b/gcc/testsuite/gfortran.dg/iso_c_binding_rename_1.f03 @@ -80,5 +80,3 @@ contains end if end subroutine sub4 end module iso_c_binding_rename_1 - -! { dg-final { cleanup-modules "iso_c_binding_rename_0 iso_c_binding_rename_1" } } diff --git a/gcc/testsuite/gfortran.dg/iso_c_binding_rename_2.f03 b/gcc/testsuite/gfortran.dg/iso_c_binding_rename_2.f03 index e7c18db2f15e..75797e78f734 100644 --- a/gcc/testsuite/gfortran.dg/iso_c_binding_rename_2.f03 +++ b/gcc/testsuite/gfortran.dg/iso_c_binding_rename_2.f03 @@ -38,5 +38,3 @@ contains end subroutine sub4 end module mod2 - -! { dg-final { cleanup-modules "mod0 mod1 mod2" } } diff --git a/gcc/testsuite/gfortran.dg/iso_fortran_env_1.f90 b/gcc/testsuite/gfortran.dg/iso_fortran_env_1.f90 index dfcf49bf9609..17e9c7ade360 100644 --- a/gcc/testsuite/gfortran.dg/iso_fortran_env_1.f90 +++ b/gcc/testsuite/gfortran.dg/iso_fortran_env_1.f90 @@ -41,4 +41,3 @@ program test call bar call bar2 end -! { dg-final { cleanup-modules "iso_fortran_env" } } diff --git a/gcc/testsuite/gfortran.dg/iso_fortran_env_2.f90 b/gcc/testsuite/gfortran.dg/iso_fortran_env_2.f90 index 6f8d228d924b..1c5f69715a12 100644 --- a/gcc/testsuite/gfortran.dg/iso_fortran_env_2.f90 +++ b/gcc/testsuite/gfortran.dg/iso_fortran_env_2.f90 @@ -72,5 +72,3 @@ subroutine gee5 use ,non_intrinsic :: iso_fortran_env print *, x end - -! { dg-final { cleanup-modules "iso_fortran_env" } } diff --git a/gcc/testsuite/gfortran.dg/iso_fortran_env_4.f90 b/gcc/testsuite/gfortran.dg/iso_fortran_env_4.f90 index 515269bd7ec1..48d13a833065 100644 --- a/gcc/testsuite/gfortran.dg/iso_fortran_env_4.f90 +++ b/gcc/testsuite/gfortran.dg/iso_fortran_env_4.f90 @@ -11,4 +11,3 @@ subroutine truc use, non_intrinsic :: iso_fortran_env use, intrinsic :: iso_fortran_env ! { dg-error "conflicts with non-intrinsic module" } end subroutine truc -! { dg-final { cleanup-modules "iso_fortran_env" } } diff --git a/gcc/testsuite/gfortran.dg/kind_tests_2.f03 b/gcc/testsuite/gfortran.dg/kind_tests_2.f03 index 2a0d7c985d8d..d740657a262f 100644 --- a/gcc/testsuite/gfortran.dg/kind_tests_2.f03 +++ b/gcc/testsuite/gfortran.dg/kind_tests_2.f03 @@ -5,5 +5,3 @@ module kind_tests_2 integer, parameter :: myFKind = c_float real(myFKind), bind(c) :: myF end module kind_tests_2 - -! { dg-final { cleanup-modules "kind_tests_2" } } diff --git a/gcc/testsuite/gfortran.dg/kind_tests_3.f03 b/gcc/testsuite/gfortran.dg/kind_tests_3.f03 index af041b0f9e6e..83cb91e95d6d 100644 --- a/gcc/testsuite/gfortran.dg/kind_tests_3.f03 +++ b/gcc/testsuite/gfortran.dg/kind_tests_3.f03 @@ -8,5 +8,3 @@ module my_module use my_kinds real(myFKind), bind(c) :: myF end module my_module - -! { dg-final { cleanup-modules "my_kinds my_module" } } diff --git a/gcc/testsuite/gfortran.dg/large_integer_kind_1.f90 b/gcc/testsuite/gfortran.dg/large_integer_kind_1.f90 index 2f272db923dc..9511317901c8 100644 --- a/gcc/testsuite/gfortran.dg/large_integer_kind_1.f90 +++ b/gcc/testsuite/gfortran.dg/large_integer_kind_1.f90 @@ -36,5 +36,3 @@ program test x = -huge(0_8) call testoutput (x,-huge(0_8),50,'(I50)') end program test - -! { dg-final { cleanup-modules "testmod" } } diff --git a/gcc/testsuite/gfortran.dg/large_real_kind_1.f90 b/gcc/testsuite/gfortran.dg/large_real_kind_1.f90 index 28e406730fa3..0d95718eb434 100644 --- a/gcc/testsuite/gfortran.dg/large_real_kind_1.f90 +++ b/gcc/testsuite/gfortran.dg/large_real_kind_1.f90 @@ -75,5 +75,3 @@ program test c2(1:1) = ' ' if (c1 /= c2) call abort end program test - -! { dg-final { cleanup-modules "testmod" } } diff --git a/gcc/testsuite/gfortran.dg/ldist-pr43023.f90 b/gcc/testsuite/gfortran.dg/ldist-pr43023.f90 index 7a298ea4b2f9..3e2d04c94901 100644 --- a/gcc/testsuite/gfortran.dg/ldist-pr43023.f90 +++ b/gcc/testsuite/gfortran.dg/ldist-pr43023.f90 @@ -29,5 +29,3 @@ end do END SUBROUTINE NFT_Init END MODULE NFT_mod - -! { dg-final { cleanup-modules "nft_mod" } } diff --git a/gcc/testsuite/gfortran.dg/lto/20100222-1_0.f03 b/gcc/testsuite/gfortran.dg/lto/20100222-1_0.f03 index fece7815430c..e94ec97d1b69 100644 --- a/gcc/testsuite/gfortran.dg/lto/20100222-1_0.f03 +++ b/gcc/testsuite/gfortran.dg/lto/20100222-1_0.f03 @@ -32,4 +32,3 @@ program main p = c_funloc(ffunc) call callFunc(p, 21,-17*21) end program main -! { dg-final { cleanup-modules "c_funloc_tests_3" } } diff --git a/gcc/testsuite/gfortran.dg/lto/pr40725_0.f03 b/gcc/testsuite/gfortran.dg/lto/pr40725_0.f03 index db783159a244..91d84bd0740f 100644 --- a/gcc/testsuite/gfortran.dg/lto/pr40725_0.f03 +++ b/gcc/testsuite/gfortran.dg/lto/pr40725_0.f03 @@ -13,5 +13,3 @@ contains end if end subroutine sub0 end module bind_c_dts_2 - -! { dg-final { cleanup-modules "bind_c_dts_2" } } diff --git a/gcc/testsuite/gfortran.dg/lto/pr45586-2_0.f90 b/gcc/testsuite/gfortran.dg/lto/pr45586-2_0.f90 index 52e2bb1e6d9f..5f9e5027a157 100644 --- a/gcc/testsuite/gfortran.dg/lto/pr45586-2_0.f90 +++ b/gcc/testsuite/gfortran.dg/lto/pr45586-2_0.f90 @@ -30,5 +30,3 @@ END MODULE USE M2 CALL S1() END - -! { dg-final { cleanup-modules "m1 m2" } } diff --git a/gcc/testsuite/gfortran.dg/lto/pr45586_0.f90 b/gcc/testsuite/gfortran.dg/lto/pr45586_0.f90 index 551ba6c4244d..84f3633df744 100644 --- a/gcc/testsuite/gfortran.dg/lto/pr45586_0.f90 +++ b/gcc/testsuite/gfortran.dg/lto/pr45586_0.f90 @@ -27,5 +27,3 @@ CALL S1(x) write(6,*) x%r END - -! { dg-final { cleanup-modules "m1 m2" } } diff --git a/gcc/testsuite/gfortran.dg/lto/pr47839_0.f90 b/gcc/testsuite/gfortran.dg/lto/pr47839_0.f90 index ec7fe3f2426e..9ea9315284a1 100644 --- a/gcc/testsuite/gfortran.dg/lto/pr47839_0.f90 +++ b/gcc/testsuite/gfortran.dg/lto/pr47839_0.f90 @@ -6,5 +6,3 @@ MODULE globalvar_mod integer :: xstop CONTAINS END MODULE globalvar_mod - -! { dg-final { cleanup-modules "globalvar_mod pec_mod" } } diff --git a/gcc/testsuite/gfortran.dg/mapping_1.f90 b/gcc/testsuite/gfortran.dg/mapping_1.f90 index 02042c026267..eda198e82846 100644 --- a/gcc/testsuite/gfortran.dg/mapping_1.f90 +++ b/gcc/testsuite/gfortran.dg/mapping_1.f90 @@ -67,4 +67,3 @@ program spec_test c_size = 5 if (tricky ('Help me', butt_ugly) .ne. transfer (butt_ugly (1), chr)) call abort () end program spec_test -! { dg-final { cleanup-modules "mykinds spec_xpr xtra_fun" } } diff --git a/gcc/testsuite/gfortran.dg/mapping_2.f90 b/gcc/testsuite/gfortran.dg/mapping_2.f90 index 9104184a59bb..1245c6640bd4 100644 --- a/gcc/testsuite/gfortran.dg/mapping_2.f90 +++ b/gcc/testsuite/gfortran.dg/mapping_2.f90 @@ -29,4 +29,3 @@ program len_test if (my_string(x) .ne. "01234567890") call abort () end program len_test -! { dg-final { cleanup-modules "test" } } diff --git a/gcc/testsuite/gfortran.dg/maxloc_bounds_4.f90 b/gcc/testsuite/gfortran.dg/maxloc_bounds_4.f90 index 7ba103d6168a..b1c7ca752d04 100644 --- a/gcc/testsuite/gfortran.dg/maxloc_bounds_4.f90 +++ b/gcc/testsuite/gfortran.dg/maxloc_bounds_4.f90 @@ -19,5 +19,3 @@ program main call foo(res) end program main ! { dg-output "Fortran runtime error: Incorrect extent in return value of MAXLOC intrinsic: is 3, should be 2" } -! { dg-final { cleanup-modules "tst" } } - diff --git a/gcc/testsuite/gfortran.dg/maxloc_bounds_5.f90 b/gcc/testsuite/gfortran.dg/maxloc_bounds_5.f90 index 34d06da55ac0..ad93d238e74d 100644 --- a/gcc/testsuite/gfortran.dg/maxloc_bounds_5.f90 +++ b/gcc/testsuite/gfortran.dg/maxloc_bounds_5.f90 @@ -19,4 +19,3 @@ program main call foo(res) end program main ! { dg-output "Fortran runtime error: Incorrect extent in return value of MAXLOC intrinsic: is 3, should be 2" } -! { dg-final { cleanup-modules "tst" } } diff --git a/gcc/testsuite/gfortran.dg/maxloc_bounds_7.f90 b/gcc/testsuite/gfortran.dg/maxloc_bounds_7.f90 index 817bf8fac399..206a29b149da 100644 --- a/gcc/testsuite/gfortran.dg/maxloc_bounds_7.f90 +++ b/gcc/testsuite/gfortran.dg/maxloc_bounds_7.f90 @@ -19,4 +19,3 @@ program main call foo(res) end program main ! { dg-output "Fortran runtime error: Incorrect extent in return value of MAXLOC intrinsic: is 3, should be 2" } -! { dg-final { cleanup-modules "tst" } } diff --git a/gcc/testsuite/gfortran.dg/missing_derived_type_1.f90 b/gcc/testsuite/gfortran.dg/missing_derived_type_1.f90 index c890927179c0..0e6623ef40ac 100644 --- a/gcc/testsuite/gfortran.dg/missing_derived_type_1.f90 +++ b/gcc/testsuite/gfortran.dg/missing_derived_type_1.f90 @@ -11,4 +11,3 @@ module test type(nonexist),pointer :: l ! { dg-error "has not been declared" } end type epot_t end module test -! { dg-final { cleanup-modules "test" } } diff --git a/gcc/testsuite/gfortran.dg/missing_optional_dummy_2.f90 b/gcc/testsuite/gfortran.dg/missing_optional_dummy_2.f90 index 100784d8704e..d6d0cf09529e 100644 --- a/gcc/testsuite/gfortran.dg/missing_optional_dummy_2.f90 +++ b/gcc/testsuite/gfortran.dg/missing_optional_dummy_2.f90 @@ -36,5 +36,3 @@ contains if (.not.present(substr)) isscan = myscan ("foo", "over") end function isscan end -! { dg-final { cleanup-modules "myint" } } - diff --git a/gcc/testsuite/gfortran.dg/missing_optional_dummy_4.f90 b/gcc/testsuite/gfortran.dg/missing_optional_dummy_4.f90 index 9b1a574d792a..30db273c5d99 100644 --- a/gcc/testsuite/gfortran.dg/missing_optional_dummy_4.f90 +++ b/gcc/testsuite/gfortran.dg/missing_optional_dummy_4.f90 @@ -24,5 +24,3 @@ end module krmod ! { dg-final { scan-tree-dump " tm_doit \\(0B, 0\\);" "original" } } ! { dg-final { cleanup-tree-dump "original" } } -! { dg-final { cleanup-modules "krmod" } } - diff --git a/gcc/testsuite/gfortran.dg/missing_optional_dummy_5.f90 b/gcc/testsuite/gfortran.dg/missing_optional_dummy_5.f90 index 29a9d70f8998..1130d43f4082 100644 --- a/gcc/testsuite/gfortran.dg/missing_optional_dummy_5.f90 +++ b/gcc/testsuite/gfortran.dg/missing_optional_dummy_5.f90 @@ -25,5 +25,3 @@ end module krmod ! { dg-final { scan-tree-dump " tm_doit \\(&parm\.., 0B, 0\\);" "original" } } ! { dg-final { cleanup-tree-dump "original" } } -! { dg-final { cleanup-modules "krmod" } } - diff --git a/gcc/testsuite/gfortran.dg/module_blank_common.f90 b/gcc/testsuite/gfortran.dg/module_blank_common.f90 index a06ff0098e00..1eab444938b9 100644 --- a/gcc/testsuite/gfortran.dg/module_blank_common.f90 +++ b/gcc/testsuite/gfortran.dg/module_blank_common.f90 @@ -15,5 +15,3 @@ program blank_common b = -999.0_4 if (z.ne.cmplx (a,b)) call abort () end program blank_common - -! { dg-final { cleanup-modules "global" } } diff --git a/gcc/testsuite/gfortran.dg/module_commons_1.f90 b/gcc/testsuite/gfortran.dg/module_commons_1.f90 index bd2c7f99be1e..73d5257f7a75 100644 --- a/gcc/testsuite/gfortran.dg/module_commons_1.f90 +++ b/gcc/testsuite/gfortran.dg/module_commons_1.f90 @@ -21,5 +21,3 @@ program collision b = 99.0 call foo () end program collision - -! { dg-final { cleanup-modules "m1 m2" } } diff --git a/gcc/testsuite/gfortran.dg/module_commons_2.f90 b/gcc/testsuite/gfortran.dg/module_commons_2.f90 index 3c3214c20ff3..a61008166e3c 100644 --- a/gcc/testsuite/gfortran.dg/module_commons_2.f90 +++ b/gcc/testsuite/gfortran.dg/module_commons_2.f90 @@ -17,5 +17,3 @@ end module h5global program bug use h5global end - -! { dg-final { cleanup-modules "h5global" } } diff --git a/gcc/testsuite/gfortran.dg/module_commons_3.f90 b/gcc/testsuite/gfortran.dg/module_commons_3.f90 index e60cf9b53099..89c71b897eb7 100644 --- a/gcc/testsuite/gfortran.dg/module_commons_3.f90 +++ b/gcc/testsuite/gfortran.dg/module_commons_3.f90 @@ -54,4 +54,3 @@ PROGRAM TEST1 call BAR (T2) CALL FOOBAR (T2) END PROGRAM TEST1 -! { dg-final { cleanup-modules "test2 test3 test4" } } diff --git a/gcc/testsuite/gfortran.dg/module_double_reuse.f90 b/gcc/testsuite/gfortran.dg/module_double_reuse.f90 index 694e821b7860..0d527f38a512 100644 --- a/gcc/testsuite/gfortran.dg/module_double_reuse.f90 +++ b/gcc/testsuite/gfortran.dg/module_double_reuse.f90 @@ -16,5 +16,3 @@ program d if (kind(x).ne.kind(y)) call abort () if (v.ne.u) call abort () end program d - -! { dg-final { cleanup-modules "a" } } diff --git a/gcc/testsuite/gfortran.dg/module_equivalence_1.f90 b/gcc/testsuite/gfortran.dg/module_equivalence_1.f90 index fecfb89fac33..50a19f2a4385 100644 --- a/gcc/testsuite/gfortran.dg/module_equivalence_1.f90 +++ b/gcc/testsuite/gfortran.dg/module_equivalence_1.f90 @@ -22,5 +22,3 @@ program module_equiv c = (/99.0_4, 999.0_4, 999.0_4, 99.0_4/) call foo () end program module_equiv - -! { dg-final { cleanup-modules "test_equiv" } } diff --git a/gcc/testsuite/gfortran.dg/module_equivalence_2.f90 b/gcc/testsuite/gfortran.dg/module_equivalence_2.f90 index f6a3c34039bb..3ec8efb41a41 100644 --- a/gcc/testsuite/gfortran.dg/module_equivalence_2.f90 +++ b/gcc/testsuite/gfortran.dg/module_equivalence_2.f90 @@ -22,4 +22,3 @@ end module b reM = 0.57d1 if (M .ne. 0.57d1) call abort () end -! { dg-final { cleanup-modules "a b" } } diff --git a/gcc/testsuite/gfortran.dg/module_equivalence_3.f90 b/gcc/testsuite/gfortran.dg/module_equivalence_3.f90 index d646f97407e5..75b90285a2cc 100644 --- a/gcc/testsuite/gfortran.dg/module_equivalence_3.f90 +++ b/gcc/testsuite/gfortran.dg/module_equivalence_3.f90 @@ -34,5 +34,3 @@ contains if (any(d(3:5) .ne. b)) call abort () end subroutine end - -! { dg-final { cleanup-modules "aap" } } diff --git a/gcc/testsuite/gfortran.dg/module_equivalence_4.f90 b/gcc/testsuite/gfortran.dg/module_equivalence_4.f90 index c30fd5205884..09eb914af06c 100644 --- a/gcc/testsuite/gfortran.dg/module_equivalence_4.f90 +++ b/gcc/testsuite/gfortran.dg/module_equivalence_4.f90 @@ -25,5 +25,3 @@ end subroutine nudata real :: a_(2) = (/1.,2./) call nudata (nlibe_, a_, l_) end - -! { dg-final { cleanup-modules "data_c" } } diff --git a/gcc/testsuite/gfortran.dg/module_equivalence_5.f90 b/gcc/testsuite/gfortran.dg/module_equivalence_5.f90 index de1d5043d79e..e5acfaaa9dcc 100644 --- a/gcc/testsuite/gfortran.dg/module_equivalence_5.f90 +++ b/gcc/testsuite/gfortran.dg/module_equivalence_5.f90 @@ -29,6 +29,3 @@ program try_cf004 nf2 = 2 call cf0004 end - -! { dg-final { cleanup-modules "stuff" } } - diff --git a/gcc/testsuite/gfortran.dg/module_equivalence_6.f90 b/gcc/testsuite/gfortran.dg/module_equivalence_6.f90 index 40e8b4b78863..67a52358e249 100644 --- a/gcc/testsuite/gfortran.dg/module_equivalence_6.f90 +++ b/gcc/testsuite/gfortran.dg/module_equivalence_6.f90 @@ -19,4 +19,3 @@ PROGRAM fortranlibtest INTEGER :: ii ii = H5P_DEFAULT_F END PROGRAM fortranlibtest -! { dg-final { cleanup-modules "h5global hdf5" } } diff --git a/gcc/testsuite/gfortran.dg/module_function_type_1.f90 b/gcc/testsuite/gfortran.dg/module_function_type_1.f90 index a1063b149632..793205cf5991 100644 --- a/gcc/testsuite/gfortran.dg/module_function_type_1.f90 +++ b/gcc/testsuite/gfortran.dg/module_function_type_1.f90 @@ -28,6 +28,3 @@ program C type(A_type):: A_var A_var = initA() end program C - -! { dg-final { cleanup-modules "a b" } } - diff --git a/gcc/testsuite/gfortran.dg/module_implicit_conversion.f90 b/gcc/testsuite/gfortran.dg/module_implicit_conversion.f90 index d7835a7f9613..9626f951b1d4 100644 --- a/gcc/testsuite/gfortran.dg/module_implicit_conversion.f90 +++ b/gcc/testsuite/gfortran.dg/module_implicit_conversion.f90 @@ -5,5 +5,3 @@ module module_implicit_conversion ! double complex :: s = (1.0D0, 0D0) double complex :: s = (1.0, 0D0) end module module_implicit_conversion - -! { dg-final { cleanup-modules "module_implicit_conversion" } } diff --git a/gcc/testsuite/gfortran.dg/module_interface_1.f90 b/gcc/testsuite/gfortran.dg/module_interface_1.f90 index 54ea14bcae2f..354aa97f649c 100644 --- a/gcc/testsuite/gfortran.dg/module_interface_1.f90 +++ b/gcc/testsuite/gfortran.dg/module_interface_1.f90 @@ -34,5 +34,3 @@ return end subroutine Selection_Sort end program module_interface - -! { dg-final { cleanup-modules "max_loc_mod" } } diff --git a/gcc/testsuite/gfortran.dg/module_interface_2.f90 b/gcc/testsuite/gfortran.dg/module_interface_2.f90 index 1f9fde81edb4..d233797da534 100644 --- a/gcc/testsuite/gfortran.dg/module_interface_2.f90 +++ b/gcc/testsuite/gfortran.dg/module_interface_2.f90 @@ -28,4 +28,3 @@ end module foo_mod print *, two (2.3) print *, dbl (2.3) end program xfoo -! { dg-final { cleanup-modules "foo_mod" } } diff --git a/gcc/testsuite/gfortran.dg/module_md5_1.f90 b/gcc/testsuite/gfortran.dg/module_md5_1.f90 index 0816a7053f50..1f522cbb915f 100644 --- a/gcc/testsuite/gfortran.dg/module_md5_1.f90 +++ b/gcc/testsuite/gfortran.dg/module_md5_1.f90 @@ -11,4 +11,3 @@ program test print *, pi end program test ! { dg-final { scan-module "foo" "MD5:510304affe70481794fecdb22fc9ca0c" } } -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/module_naming_1.f90 b/gcc/testsuite/gfortran.dg/module_naming_1.f90 index 8024300fb004..2a2d00b1d30a 100644 --- a/gcc/testsuite/gfortran.dg/module_naming_1.f90 +++ b/gcc/testsuite/gfortran.dg/module_naming_1.f90 @@ -29,4 +29,3 @@ contains ! mangled to __m2_mod_m2_MOD_m3 end subroutine m3 end module m2_MOD_m2 -! { dg-final { cleanup-modules "m1 m1__m2 m2 m2_mod_m2" } } diff --git a/gcc/testsuite/gfortran.dg/module_nan.f90 b/gcc/testsuite/gfortran.dg/module_nan.f90 index 202781f07c2f..5f41514bc0b0 100644 --- a/gcc/testsuite/gfortran.dg/module_nan.f90 +++ b/gcc/testsuite/gfortran.dg/module_nan.f90 @@ -26,5 +26,3 @@ program a write(str,*) nan if (adjustl(str) /= "NaN") call abort() end program a - -! { dg-final { cleanup-modules "nonordinal" } } diff --git a/gcc/testsuite/gfortran.dg/module_parameter_array_refs_1.f90 b/gcc/testsuite/gfortran.dg/module_parameter_array_refs_1.f90 index 592e2f3dd2a2..9ef75d9e6910 100644 --- a/gcc/testsuite/gfortran.dg/module_parameter_array_refs_1.f90 +++ b/gcc/testsuite/gfortran.dg/module_parameter_array_refs_1.f90 @@ -10,5 +10,3 @@ module foo integer :: arr(max(len,1)) end - -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/module_parameter_array_refs_2.f90 b/gcc/testsuite/gfortran.dg/module_parameter_array_refs_2.f90 index 385761d1d170..7324ff6c51e6 100644 --- a/gcc/testsuite/gfortran.dg/module_parameter_array_refs_2.f90 +++ b/gcc/testsuite/gfortran.dg/module_parameter_array_refs_2.f90 @@ -19,5 +19,3 @@ integer :: i i = 1 if (para(i) /= 1) call i_am_optimized_away() end - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/module_private_1.f90 b/gcc/testsuite/gfortran.dg/module_private_1.f90 index 7d854a1a9517..66bc56405b08 100644 --- a/gcc/testsuite/gfortran.dg/module_private_1.f90 +++ b/gcc/testsuite/gfortran.dg/module_private_1.f90 @@ -18,5 +18,3 @@ program main j = 1 print *, i, j end program main - -! { dg-final { cleanup-modules "bar foo" } } diff --git a/gcc/testsuite/gfortran.dg/module_private_array_refs_1.f90 b/gcc/testsuite/gfortran.dg/module_private_array_refs_1.f90 index e2591ab4b6d6..56bd6f261e71 100644 --- a/gcc/testsuite/gfortran.dg/module_private_array_refs_1.f90 +++ b/gcc/testsuite/gfortran.dg/module_private_array_refs_1.f90 @@ -48,5 +48,3 @@ end use bar call sub () end - -! { dg-final { cleanup-modules "foo bar" } } diff --git a/gcc/testsuite/gfortran.dg/module_proc_external_dummy.f90 b/gcc/testsuite/gfortran.dg/module_proc_external_dummy.f90 index 86c66c2fadc6..08f61b05f6f3 100644 --- a/gcc/testsuite/gfortran.dg/module_proc_external_dummy.f90 +++ b/gcc/testsuite/gfortran.dg/module_proc_external_dummy.f90 @@ -27,4 +27,3 @@ end module test_module call sub_module (sub) call sub_module (str) end -! { dg-final { cleanup-modules "test_module" } } diff --git a/gcc/testsuite/gfortran.dg/module_procedure_1.f90 b/gcc/testsuite/gfortran.dg/module_procedure_1.f90 index 5e1fa15c729f..35ec18c0b61e 100644 --- a/gcc/testsuite/gfortran.dg/module_procedure_1.f90 +++ b/gcc/testsuite/gfortran.dg/module_procedure_1.f90 @@ -50,4 +50,3 @@ subroutine test_sub(input1, input2) if (mysum(1) /= 3 .and. mysum(2) /= 4) call abort end subroutine test_sub -! { dg-final { cleanup-modules "myoperator" } } diff --git a/gcc/testsuite/gfortran.dg/module_procedure_double_colon_1.f90 b/gcc/testsuite/gfortran.dg/module_procedure_double_colon_1.f90 index 200f0ff26e1b..3987759f9905 100644 --- a/gcc/testsuite/gfortran.dg/module_procedure_double_colon_1.f90 +++ b/gcc/testsuite/gfortran.dg/module_procedure_double_colon_1.f90 @@ -20,4 +20,3 @@ contains real x end subroutine end module -! { dg-final { cleanup-modules "m1" } } diff --git a/gcc/testsuite/gfortran.dg/module_procedure_double_colon_2.f90 b/gcc/testsuite/gfortran.dg/module_procedure_double_colon_2.f90 index 9300215e7492..b59e766f072f 100644 --- a/gcc/testsuite/gfortran.dg/module_procedure_double_colon_2.f90 +++ b/gcc/testsuite/gfortran.dg/module_procedure_double_colon_2.f90 @@ -21,4 +21,3 @@ contains real x end subroutine end module -! { dg-final { cleanup-modules "m1" } } diff --git a/gcc/testsuite/gfortran.dg/module_read_1.f90 b/gcc/testsuite/gfortran.dg/module_read_1.f90 index 226c7366cd26..ad3e3d1dcde3 100644 --- a/gcc/testsuite/gfortran.dg/module_read_1.f90 +++ b/gcc/testsuite/gfortran.dg/module_read_1.f90 @@ -27,4 +27,3 @@ program test if(len(push(0)) /= 0) call abort() if(len(push(1)) /= 1) call abort() end program -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/module_read_2.f90 b/gcc/testsuite/gfortran.dg/module_read_2.f90 index d001ca7589bd..565c188f88f6 100644 --- a/gcc/testsuite/gfortran.dg/module_read_2.f90 +++ b/gcc/testsuite/gfortran.dg/module_read_2.f90 @@ -26,5 +26,3 @@ str%string = ['H','e','l','l','o'] if (len (string_to_char (str)) /= 5) call abort () if (string_to_char (str) /= "Hello") call abort () end - -! { dg-final { cleanup-modules "m_string" } } diff --git a/gcc/testsuite/gfortran.dg/module_widestring_1.f90 b/gcc/testsuite/gfortran.dg/module_widestring_1.f90 index f2e9fe23526e..c34091015db9 100644 --- a/gcc/testsuite/gfortran.dg/module_widestring_1.f90 +++ b/gcc/testsuite/gfortran.dg/module_widestring_1.f90 @@ -12,5 +12,3 @@ end module m if (ichar(a(2:2)) /= 0) call abort write (s,"(A)") a end - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/module_write_1.f90 b/gcc/testsuite/gfortran.dg/module_write_1.f90 index 3b488ce55d9a..0613c92e1618 100644 --- a/gcc/testsuite/gfortran.dg/module_write_1.f90 +++ b/gcc/testsuite/gfortran.dg/module_write_1.f90 @@ -56,4 +56,3 @@ use FoX_dom implicit none print *, vs_str("ABC") end -! { dg-final { cleanup-modules "fox_m_fsys_array_str fox_m_fsys_format m_dom_dom fox_dom" } } diff --git a/gcc/testsuite/gfortran.dg/move_alloc_10.f90 b/gcc/testsuite/gfortran.dg/move_alloc_10.f90 index 3a538be456cf..e5979287af62 100644 --- a/gcc/testsuite/gfortran.dg/move_alloc_10.f90 +++ b/gcc/testsuite/gfortran.dg/move_alloc_10.f90 @@ -75,5 +75,3 @@ program main call abort () end select end program main - -! { dg-final { cleanup-modules "myalloc" } } diff --git a/gcc/testsuite/gfortran.dg/move_alloc_8.f90 b/gcc/testsuite/gfortran.dg/move_alloc_8.f90 index 2fa530666004..f624b703cc95 100644 --- a/gcc/testsuite/gfortran.dg/move_alloc_8.f90 +++ b/gcc/testsuite/gfortran.dg/move_alloc_8.f90 @@ -102,5 +102,3 @@ CONTAINS call move_alloc(dt%VALUE, lv) ! { dg-error "cannot be INTENT.IN." } END SUBROUTINE end subroutine test4 - -! { dg-final { cleanup-modules "bug" } } diff --git a/gcc/testsuite/gfortran.dg/move_alloc_9.f90 b/gcc/testsuite/gfortran.dg/move_alloc_9.f90 index 60d6f1496e2a..bf3f7b1b73f4 100644 --- a/gcc/testsuite/gfortran.dg/move_alloc_9.f90 +++ b/gcc/testsuite/gfortran.dg/move_alloc_9.f90 @@ -53,5 +53,3 @@ program testmv1 if (allocated(sm2)) call abort() if (.not. allocated(sm)) call abort() end program - -! { dg-final { cleanup-modules "m2 m3" } } diff --git a/gcc/testsuite/gfortran.dg/mvbits_6.f90 b/gcc/testsuite/gfortran.dg/mvbits_6.f90 index 56ceacc5ec8e..c8986df21ca1 100644 --- a/gcc/testsuite/gfortran.dg/mvbits_6.f90 +++ b/gcc/testsuite/gfortran.dg/mvbits_6.f90 @@ -31,4 +31,3 @@ call yg0009(tda2l,4,3,1,-1,-4,-3) end -! { dg-final { cleanup-modules "yg0009_stuff" } } diff --git a/gcc/testsuite/gfortran.dg/named_interface.f90 b/gcc/testsuite/gfortran.dg/named_interface.f90 index 29cfae882758..90fea809fb0c 100644 --- a/gcc/testsuite/gfortran.dg/named_interface.f90 +++ b/gcc/testsuite/gfortran.dg/named_interface.f90 @@ -7,5 +7,3 @@ module snafu end subroutine really_snafu end interface foo end module snafu - -! { dg-final { cleanup-modules "snafu" } } diff --git a/gcc/testsuite/gfortran.dg/namelist_1.f90 b/gcc/testsuite/gfortran.dg/namelist_1.f90 index e4154e9181b5..ee028dd0e5e6 100644 --- a/gcc/testsuite/gfortran.dg/namelist_1.f90 +++ b/gcc/testsuite/gfortran.dg/namelist_1.f90 @@ -5,5 +5,3 @@ module namelist_1 integer,private :: x namelist /n/ x ! { dg-error "cannot be member of PUBLIC namelist" "" } end module - -! { dg-final { cleanup-modules "namelist_1" } } diff --git a/gcc/testsuite/gfortran.dg/namelist_14.f90 b/gcc/testsuite/gfortran.dg/namelist_14.f90 index 478e07fe67fe..341d1a3e98d4 100644 --- a/gcc/testsuite/gfortran.dg/namelist_14.f90 +++ b/gcc/testsuite/gfortran.dg/namelist_14.f90 @@ -95,5 +95,3 @@ contains end subroutine foo end program namelist_14 - -! { dg-final { cleanup-modules "global" } } diff --git a/gcc/testsuite/gfortran.dg/namelist_15.f90 b/gcc/testsuite/gfortran.dg/namelist_15.f90 index e900e71d1432..ea02f9f7afab 100644 --- a/gcc/testsuite/gfortran.dg/namelist_15.f90 +++ b/gcc/testsuite/gfortran.dg/namelist_15.f90 @@ -61,5 +61,3 @@ program namelist_15 (x(2)%m(2)%ch(2) == "kz"))) call abort () end program namelist_15 - -! { dg-final { cleanup-modules "global" } } diff --git a/gcc/testsuite/gfortran.dg/namelist_33.f90 b/gcc/testsuite/gfortran.dg/namelist_33.f90 index 8bbe59715edd..79459eecef7f 100644 --- a/gcc/testsuite/gfortran.dg/namelist_33.f90 +++ b/gcc/testsuite/gfortran.dg/namelist_33.f90 @@ -66,5 +66,3 @@ contains namelist /nml2/ t5 ! { dg-error "has use-associated PRIVATE components" } end subroutine end program - -! { dg-final { cleanup-modules "types nml" } } diff --git a/gcc/testsuite/gfortran.dg/namelist_34.f90 b/gcc/testsuite/gfortran.dg/namelist_34.f90 index f7c5e1cf6f15..94327710d38f 100644 --- a/gcc/testsuite/gfortran.dg/namelist_34.f90 +++ b/gcc/testsuite/gfortran.dg/namelist_34.f90 @@ -26,5 +26,3 @@ USE types namelist /a/ t1 ! { dg-error "has ALLOCATABLE or POINTER components and thus requires a defined input/output" } namelist /b/ t3 ! { dg-error "has ALLOCATABLE or POINTER components and thus requires a defined input/output" } END MODULE - -! { dg-final { cleanup-modules "types nml" } } diff --git a/gcc/testsuite/gfortran.dg/namelist_36.f90 b/gcc/testsuite/gfortran.dg/namelist_36.f90 index b6a14e36bc3f..83f420e8432c 100644 --- a/gcc/testsuite/gfortran.dg/namelist_36.f90 +++ b/gcc/testsuite/gfortran.dg/namelist_36.f90 @@ -25,5 +25,3 @@ contains namelist /nml3/ t2 ! ok, private components end subroutine END MODULE - -! { dg-final { cleanup-modules "nml" } } diff --git a/gcc/testsuite/gfortran.dg/namelist_4.f90 b/gcc/testsuite/gfortran.dg/namelist_4.f90 index ad4e1ab62db6..538bceaa4b61 100644 --- a/gcc/testsuite/gfortran.dg/namelist_4.f90 +++ b/gcc/testsuite/gfortran.dg/namelist_4.f90 @@ -38,4 +38,3 @@ CONTAINS END FUNCTION END -! { dg-final { cleanup-modules "m1" } } diff --git a/gcc/testsuite/gfortran.dg/namelist_40.f90 b/gcc/testsuite/gfortran.dg/namelist_40.f90 index d6f896a39569..195a78b64d0b 100644 --- a/gcc/testsuite/gfortran.dg/namelist_40.f90 +++ b/gcc/testsuite/gfortran.dg/namelist_40.f90 @@ -51,4 +51,3 @@ end program namelist_40 ! { dg-output "Missing colon in substring qualifier for namelist variable x%m%ch(\n|\r\n|\r)" } ! { dg-output "Substring out of range for namelist variable x%m%ch(\n|\r\n|\r)" } ! { dg-output "Bad character in substring qualifier for namelist variable x%m%ch(\n|\r\n|\r)" } -! { dg-final { cleanup-modules "global" } } diff --git a/gcc/testsuite/gfortran.dg/namelist_47.f90 b/gcc/testsuite/gfortran.dg/namelist_47.f90 index 581924720bdc..45f3823552e5 100644 --- a/gcc/testsuite/gfortran.dg/namelist_47.f90 +++ b/gcc/testsuite/gfortran.dg/namelist_47.f90 @@ -49,4 +49,3 @@ end program namelist_47 ! { dg-output "Missing colon in substring qualifier for namelist variable x%m%c012345678901234567890123456789012345678901234567890123456789h(\n|\r\n|\r)" } ! { dg-output "Substring out of range for namelist variable x%m%c012345678901234567890123456789012345678901234567890123456789h(\n|\r\n|\r)" } ! { dg-output "Bad character in substring qualifier for namelist variable x%m%c012345678901234567890123456789012345678901234567890123456789h(\n|\r\n|\r)" } -! { dg-final { cleanup-modules "nml_47" } } diff --git a/gcc/testsuite/gfortran.dg/namelist_52.f90 b/gcc/testsuite/gfortran.dg/namelist_52.f90 index 253bd3fc9a1a..6e31382927f4 100644 --- a/gcc/testsuite/gfortran.dg/namelist_52.f90 +++ b/gcc/testsuite/gfortran.dg/namelist_52.f90 @@ -30,5 +30,3 @@ read(31,nml=info_adjoint) if (adjoint%solver_type /= 'direct') call abort if (adjoint%screen_io_fs_ntime%begin /= 42) call abort end program gfortran_error_2 - -! { dg-final { cleanup-modules "mod1" } } diff --git a/gcc/testsuite/gfortran.dg/namelist_62.f90 b/gcc/testsuite/gfortran.dg/namelist_62.f90 index 23e256207664..eb7f4a84c66c 100644 --- a/gcc/testsuite/gfortran.dg/namelist_62.f90 +++ b/gcc/testsuite/gfortran.dg/namelist_62.f90 @@ -16,5 +16,3 @@ PROGRAM gafortran NAMELIST /ga/ nichflg READ (23, nml=ga) END PROGRAM gafortran - -! { dg-final { cleanup-modules "ga_commons" } } diff --git a/gcc/testsuite/gfortran.dg/namelist_use.f90 b/gcc/testsuite/gfortran.dg/namelist_use.f90 index d550e00aa6d4..d7e6272330f0 100644 --- a/gcc/testsuite/gfortran.dg/namelist_use.f90 +++ b/gcc/testsuite/gfortran.dg/namelist_use.f90 @@ -29,5 +29,3 @@ program namelist_use close (10) end program namelist_use - -! { dg-final { cleanup-modules "global" } } diff --git a/gcc/testsuite/gfortran.dg/namelist_use_only.f90 b/gcc/testsuite/gfortran.dg/namelist_use_only.f90 index d9a28a8567b2..d2a533e6d650 100644 --- a/gcc/testsuite/gfortran.dg/namelist_use_only.f90 +++ b/gcc/testsuite/gfortran.dg/namelist_use_only.f90 @@ -34,5 +34,3 @@ program namelist_use_only if ((i.ne.0).or.(rrrr.ne.3.5).or.foo()) call abort () close (10) end program namelist_use_only - -! { dg-final { cleanup-modules "global" } } diff --git a/gcc/testsuite/gfortran.dg/nan_1.f90 b/gcc/testsuite/gfortran.dg/nan_1.f90 index 609780d69d16..4ff1b873f0c4 100644 --- a/gcc/testsuite/gfortran.dg/nan_1.f90 +++ b/gcc/testsuite/gfortran.dg/nan_1.f90 @@ -122,5 +122,3 @@ program test if (isinf(max(-large, -inf, nan))) call abort end program test - -! { dg-final { cleanup-modules "aux2" } } diff --git a/gcc/testsuite/gfortran.dg/nan_2.f90 b/gcc/testsuite/gfortran.dg/nan_2.f90 index 5c821d6513e2..709b14718308 100644 --- a/gcc/testsuite/gfortran.dg/nan_2.f90 +++ b/gcc/testsuite/gfortran.dg/nan_2.f90 @@ -105,4 +105,3 @@ program test if (isinf(max(-large, -inf, nan))) call abort end program test -! { dg-final { cleanup-modules "aux2" } } diff --git a/gcc/testsuite/gfortran.dg/nested_forall_1.f b/gcc/testsuite/gfortran.dg/nested_forall_1.f index 6aa66ee97a7c..bf93b6b81c8c 100644 --- a/gcc/testsuite/gfortran.dg/nested_forall_1.f +++ b/gcc/testsuite/gfortran.dg/nested_forall_1.f @@ -35,4 +35,3 @@ END FORALL END SUBROUTINE END MODULE TESTS -! { dg-final { cleanup-modules "tests" } } diff --git a/gcc/testsuite/gfortran.dg/nested_modules_1.f90 b/gcc/testsuite/gfortran.dg/nested_modules_1.f90 index a0bd9636144b..336467f60987 100644 --- a/gcc/testsuite/gfortran.dg/nested_modules_1.f90 +++ b/gcc/testsuite/gfortran.dg/nested_modules_1.f90 @@ -41,5 +41,3 @@ call eyeore () call tigger (w) end - -! { dg-final { cleanup-modules "mod0 mod1 mod2" } } diff --git a/gcc/testsuite/gfortran.dg/nested_modules_2.f90 b/gcc/testsuite/gfortran.dg/nested_modules_2.f90 index 0714eedee6ad..deb980e39a6b 100644 --- a/gcc/testsuite/gfortran.dg/nested_modules_2.f90 +++ b/gcc/testsuite/gfortran.dg/nested_modules_2.f90 @@ -35,5 +35,3 @@ program testfoobar call sub2 (l) if (any (l.ne.(/84,42,0/))) call abort () end program testfoobar - -! { dg-final { cleanup-modules "foo bar foobar" } } diff --git a/gcc/testsuite/gfortran.dg/nested_modules_3.f90 b/gcc/testsuite/gfortran.dg/nested_modules_3.f90 index 7550368bcd93..364460c61382 100644 --- a/gcc/testsuite/gfortran.dg/nested_modules_3.f90 +++ b/gcc/testsuite/gfortran.dg/nested_modules_3.f90 @@ -53,5 +53,3 @@ PROGRAM use_foobar CALL sub3 (z, j) IF (ALL (j.ne.(/3,2,1/))) CALL abort () END PROGRAM use_foobar - -! { dg-final { cleanup-modules "foo bar foobar" } } diff --git a/gcc/testsuite/gfortran.dg/nested_modules_4.f90 b/gcc/testsuite/gfortran.dg/nested_modules_4.f90 index 6be77b36760f..f78b16fa7b9d 100644 --- a/gcc/testsuite/gfortran.dg/nested_modules_4.f90 +++ b/gcc/testsuite/gfortran.dg/nested_modules_4.f90 @@ -24,5 +24,3 @@ end module serial character*15 :: buffer buffer = lc ("Have a Nice DAY") end - -! { dg-final { cleanup-modules "string serial" } } diff --git a/gcc/testsuite/gfortran.dg/nested_modules_5.f90 b/gcc/testsuite/gfortran.dg/nested_modules_5.f90 index 2ed68244ede7..90a55819dbe7 100644 --- a/gcc/testsuite/gfortran.dg/nested_modules_5.f90 +++ b/gcc/testsuite/gfortran.dg/nested_modules_5.f90 @@ -25,5 +25,3 @@ end module serial character*15 :: buffer buffer = lc ("Have a Nice DAY") end - -! { dg-final { cleanup-modules "anything serial" } } diff --git a/gcc/testsuite/gfortran.dg/nested_modules_6.f90 b/gcc/testsuite/gfortran.dg/nested_modules_6.f90 index ab9cc2e80369..b95742270bf2 100644 --- a/gcc/testsuite/gfortran.dg/nested_modules_6.f90 +++ b/gcc/testsuite/gfortran.dg/nested_modules_6.f90 @@ -32,4 +32,3 @@ end module vamp_rest print *, s_last print *, diag (x) end -! { dg-final { cleanup-modules "tao_random_numbers linalg vamp_rest" } } diff --git a/gcc/testsuite/gfortran.dg/operator_1.f90 b/gcc/testsuite/gfortran.dg/operator_1.f90 index 1800b68e3612..6f27246d731c 100644 --- a/gcc/testsuite/gfortran.dg/operator_1.f90 +++ b/gcc/testsuite/gfortran.dg/operator_1.f90 @@ -66,4 +66,3 @@ end module m1 if (any((ac*bc) /= matmul(ac,bc))) call abort() end -! { dg-final { cleanup-modules "m1" } } diff --git a/gcc/testsuite/gfortran.dg/operator_2.f90 b/gcc/testsuite/gfortran.dg/operator_2.f90 index 0e560dad7945..11540caaf8af 100644 --- a/gcc/testsuite/gfortran.dg/operator_2.f90 +++ b/gcc/testsuite/gfortran.dg/operator_2.f90 @@ -38,4 +38,3 @@ contains end function f3 end -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/operator_4.f90 b/gcc/testsuite/gfortran.dg/operator_4.f90 index 39cd7ebdf01e..f1315034230e 100644 --- a/gcc/testsuite/gfortran.dg/operator_4.f90 +++ b/gcc/testsuite/gfortran.dg/operator_4.f90 @@ -96,5 +96,3 @@ PROGRAM pr17711 A = (A > C) ! { dg-error "comparison operator '>'" } A = (A.GT.C) ! { dg-error "comparison operator '.gt.'" } END PROGRAM - -! { dg-final { cleanup-modules "mod_t" } } diff --git a/gcc/testsuite/gfortran.dg/operator_5.f90 b/gcc/testsuite/gfortran.dg/operator_5.f90 index 6ce77c8dc4dd..307b341ad1a4 100644 --- a/gcc/testsuite/gfortran.dg/operator_5.f90 +++ b/gcc/testsuite/gfortran.dg/operator_5.f90 @@ -47,5 +47,3 @@ CONTAINS t_bar = .FALSE. END FUNCTION END MODULE - -! { dg-final { cleanup-modules "mod_t" } } diff --git a/gcc/testsuite/gfortran.dg/operator_6.f90 b/gcc/testsuite/gfortran.dg/operator_6.f90 index f7b4693f58f6..5ca2d609bfad 100644 --- a/gcc/testsuite/gfortran.dg/operator_6.f90 +++ b/gcc/testsuite/gfortran.dg/operator_6.f90 @@ -9,4 +9,3 @@ end module foo program test use foo, only : operator(.none.) ! { dg-error "not found in module" } end program test -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/operator_7.f90 b/gcc/testsuite/gfortran.dg/operator_7.f90 index 66d8dd187eec..a2a81e335c4a 100644 --- a/gcc/testsuite/gfortran.dg/operator_7.f90 +++ b/gcc/testsuite/gfortran.dg/operator_7.f90 @@ -23,5 +23,3 @@ end module type(foo) :: a, b print *, a == b end subroutine - -! { dg-final { cleanup-modules "foo_type" } } diff --git a/gcc/testsuite/gfortran.dg/operator_c1202.f90 b/gcc/testsuite/gfortran.dg/operator_c1202.f90 index ae5e1263b1a1..c53079ac5d84 100644 --- a/gcc/testsuite/gfortran.dg/operator_c1202.f90 +++ b/gcc/testsuite/gfortran.dg/operator_c1202.f90 @@ -66,5 +66,3 @@ module op end function f1 end module op - -! { dg-final { cleanup-modules "op" } } diff --git a/gcc/testsuite/gfortran.dg/optional_assumed_charlen_1.f90 b/gcc/testsuite/gfortran.dg/optional_assumed_charlen_1.f90 index 90631aa616e5..5c929e8ae39c 100644 --- a/gcc/testsuite/gfortran.dg/optional_assumed_charlen_1.f90 +++ b/gcc/testsuite/gfortran.dg/optional_assumed_charlen_1.f90 @@ -17,4 +17,3 @@ END SUBROUTINE sub2 END MODULE foo -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/optional_dim_3.f90 b/gcc/testsuite/gfortran.dg/optional_dim_3.f90 index 45099a30735d..fc66ba5b843a 100644 --- a/gcc/testsuite/gfortran.dg/optional_dim_3.f90 +++ b/gcc/testsuite/gfortran.dg/optional_dim_3.f90 @@ -50,4 +50,3 @@ program main call sub(bound=.false., dimmy=1_8) call sub() end program main -! { dg-final { cleanup-modules "tst_foo" } } diff --git a/gcc/testsuite/gfortran.dg/overload_1.f90 b/gcc/testsuite/gfortran.dg/overload_1.f90 index fc38a6c90fec..97aa8433510f 100644 --- a/gcc/testsuite/gfortran.dg/overload_1.f90 +++ b/gcc/testsuite/gfortran.dg/overload_1.f90 @@ -181,4 +181,3 @@ contains & abort end subroutine checku end program main -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/parameter_array_init_3.f90 b/gcc/testsuite/gfortran.dg/parameter_array_init_3.f90 index e39da8e8063a..6eaa98e801eb 100644 --- a/gcc/testsuite/gfortran.dg/parameter_array_init_3.f90 +++ b/gcc/testsuite/gfortran.dg/parameter_array_init_3.f90 @@ -13,4 +13,3 @@ module abuse_mod integer(1), parameter :: MSKa1(len(HEX1)) = [(1,i=1,len(HEX1))] integer(1), parameter :: ARR1(len(HEX1)) = [( MSKa1(i), i=1,len(HEX1) )] end module abuse_mod -! { dg-final { cleanup-modules "abuse_mod" } } diff --git a/gcc/testsuite/gfortran.dg/parameter_array_init_5.f90 b/gcc/testsuite/gfortran.dg/parameter_array_init_5.f90 index 2977b88af77f..0f4127af2718 100644 --- a/gcc/testsuite/gfortran.dg/parameter_array_init_5.f90 +++ b/gcc/testsuite/gfortran.dg/parameter_array_init_5.f90 @@ -23,4 +23,3 @@ program TEST use bug3 call sr end program TEST -! { dg-final { cleanup-modules "bug3" } } diff --git a/gcc/testsuite/gfortran.dg/parameter_array_section_1.f90 b/gcc/testsuite/gfortran.dg/parameter_array_section_1.f90 index 6c6959332625..30c7abd83429 100644 --- a/gcc/testsuite/gfortran.dg/parameter_array_section_1.f90 +++ b/gcc/testsuite/gfortran.dg/parameter_array_section_1.f90 @@ -21,4 +21,3 @@ end module gfcbug45 use gfcbug45 call foo end -! { dg-final { cleanup-modules "gfcbug45" } } diff --git a/gcc/testsuite/gfortran.dg/parens_5.f90 b/gcc/testsuite/gfortran.dg/parens_5.f90 index ac631ef08af4..91c58d006d84 100644 --- a/gcc/testsuite/gfortran.dg/parens_5.f90 +++ b/gcc/testsuite/gfortran.dg/parens_5.f90 @@ -19,5 +19,3 @@ program test c = bobo(5) if (c .ne. "12345") call abort end program test - -! { dg-final { cleanup-modules "para" } } diff --git a/gcc/testsuite/gfortran.dg/parens_7.f90 b/gcc/testsuite/gfortran.dg/parens_7.f90 index 9cf9e5b84e6a..5060e7a80d27 100644 --- a/gcc/testsuite/gfortran.dg/parens_7.f90 +++ b/gcc/testsuite/gfortran.dg/parens_7.f90 @@ -15,5 +15,3 @@ end function test4 end program test - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/parent_result_ref_4.f90 b/gcc/testsuite/gfortran.dg/parent_result_ref_4.f90 index 174d64569348..d8c84e7cd6bd 100644 --- a/gcc/testsuite/gfortran.dg/parent_result_ref_4.f90 +++ b/gcc/testsuite/gfortran.dg/parent_result_ref_4.f90 @@ -20,5 +20,3 @@ end module m use m if (f ().ne.2) call abort () end - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/pointer_check_6.f90 b/gcc/testsuite/gfortran.dg/pointer_check_6.f90 index 2f7373fe6ba2..81dbae847a86 100644 --- a/gcc/testsuite/gfortran.dg/pointer_check_6.f90 +++ b/gcc/testsuite/gfortran.dg/pointer_check_6.f90 @@ -113,6 +113,3 @@ contains integer :: b end subroutine end - - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/pointer_check_7.f90 b/gcc/testsuite/gfortran.dg/pointer_check_7.f90 index 0f6dcdc87fc4..5b0c212cb7de 100644 --- a/gcc/testsuite/gfortran.dg/pointer_check_7.f90 +++ b/gcc/testsuite/gfortran.dg/pointer_check_7.f90 @@ -32,5 +32,3 @@ contains end subroutine end module - -! { dg-final { cleanup-modules "base_mat_mod" } } diff --git a/gcc/testsuite/gfortran.dg/pointer_comp_init_1.f90 b/gcc/testsuite/gfortran.dg/pointer_comp_init_1.f90 index 44f360e98261..5738de6c9fca 100644 --- a/gcc/testsuite/gfortran.dg/pointer_comp_init_1.f90 +++ b/gcc/testsuite/gfortran.dg/pointer_comp_init_1.f90 @@ -26,5 +26,3 @@ contains end subroutine add_item_to_dict end module m_common_attrs - -! { dg-final { cleanup-modules "m_common_attrs" } } diff --git a/gcc/testsuite/gfortran.dg/pointer_init_3.f90 b/gcc/testsuite/gfortran.dg/pointer_init_3.f90 index 867a428bf489..a91e518cc4b4 100644 --- a/gcc/testsuite/gfortran.dg/pointer_init_3.f90 +++ b/gcc/testsuite/gfortran.dg/pointer_init_3.f90 @@ -40,5 +40,3 @@ dp3 = 4 if (u%i/=4) call abort() end - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/pointer_init_4.f90 b/gcc/testsuite/gfortran.dg/pointer_init_4.f90 index 75ead4529170..2ca173468d8e 100644 --- a/gcc/testsuite/gfortran.dg/pointer_init_4.f90 +++ b/gcc/testsuite/gfortran.dg/pointer_init_4.f90 @@ -38,5 +38,3 @@ if (pp()/=42) call abort() if (u%ppc()/=43) call abort() end - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/pointer_init_5.f90 b/gcc/testsuite/gfortran.dg/pointer_init_5.f90 index beedad27d1ee..1ca773874a27 100644 --- a/gcc/testsuite/gfortran.dg/pointer_init_5.f90 +++ b/gcc/testsuite/gfortran.dg/pointer_init_5.f90 @@ -38,5 +38,3 @@ if (pp()/=42) call abort() if (u%ppc()/=43) call abort() end - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/pointer_init_6.f90 b/gcc/testsuite/gfortran.dg/pointer_init_6.f90 index cc5cf3600553..428a7dee8447 100644 --- a/gcc/testsuite/gfortran.dg/pointer_init_6.f90 +++ b/gcc/testsuite/gfortran.dg/pointer_init_6.f90 @@ -35,5 +35,3 @@ contains end subroutine end module m2 - -! { dg-final { cleanup-modules "m1 m2" } } diff --git a/gcc/testsuite/gfortran.dg/pr15164.f90 b/gcc/testsuite/gfortran.dg/pr15164.f90 index f8098710beec..def29318e1b4 100644 --- a/gcc/testsuite/gfortran.dg/pr15164.f90 +++ b/gcc/testsuite/gfortran.dg/pr15164.f90 @@ -13,5 +13,3 @@ return end subroutine split end module specfiles - -! { dg-final { cleanup-modules "specfiles" } } diff --git a/gcc/testsuite/gfortran.dg/pr16861.f90 b/gcc/testsuite/gfortran.dg/pr16861.f90 index 88f89fa78b5b..4a73edaf4f03 100644 --- a/gcc/testsuite/gfortran.dg/pr16861.f90 +++ b/gcc/testsuite/gfortran.dg/pr16861.f90 @@ -30,5 +30,3 @@ end subroutine quus program test call quus end program test - -! { dg-final { cleanup-modules "foo bar" } } diff --git a/gcc/testsuite/gfortran.dg/pr17615.f90 b/gcc/testsuite/gfortran.dg/pr17615.f90 index 76676182f4c2..13b90334a7b9 100644 --- a/gcc/testsuite/gfortran.dg/pr17615.f90 +++ b/gcc/testsuite/gfortran.dg/pr17615.f90 @@ -17,5 +17,3 @@ PROGRAM TEST real(8) :: c(3) c = cross_product() END PROGRAM TEST - -! { dg-final { cleanup-modules "module_vec3d" } } diff --git a/gcc/testsuite/gfortran.dg/pr19926.f90 b/gcc/testsuite/gfortran.dg/pr19926.f90 index ae70d5b0fa84..3b452c1cf65a 100644 --- a/gcc/testsuite/gfortran.dg/pr19926.f90 +++ b/gcc/testsuite/gfortran.dg/pr19926.f90 @@ -22,5 +22,3 @@ subroutine string_comp(i) integer :: i i = map(42) end subroutine string_comp - -! { dg-final { cleanup-modules "b" } } diff --git a/gcc/testsuite/gfortran.dg/pr21177.f90 b/gcc/testsuite/gfortran.dg/pr21177.f90 index 48d353123183..8ce0180dfc17 100644 --- a/gcc/testsuite/gfortran.dg/pr21177.f90 +++ b/gcc/testsuite/gfortran.dg/pr21177.f90 @@ -51,5 +51,3 @@ program test if (tt(null(c4)) /= 3) call abort() if (tt(null(c8)) /= 4) call abort() end program test - -! { dg-final { cleanup-modules "mymod" } } diff --git a/gcc/testsuite/gfortran.dg/pr25923.f90 b/gcc/testsuite/gfortran.dg/pr25923.f90 index e0df5b0c81e6..3283ba21f320 100644 --- a/gcc/testsuite/gfortran.dg/pr25923.f90 +++ b/gcc/testsuite/gfortran.dg/pr25923.f90 @@ -22,5 +22,3 @@ contains end function baz ! { dg-warning "res.yr' may be" } end module foo - -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/pr26246_1.f90 b/gcc/testsuite/gfortran.dg/pr26246_1.f90 index e35bcaca3094..a1cb45535fe0 100644 --- a/gcc/testsuite/gfortran.dg/pr26246_1.f90 +++ b/gcc/testsuite/gfortran.dg/pr26246_1.f90 @@ -16,4 +16,3 @@ end module pr26246_1 ! { dg-final { scan-tree-dump-times "static int" 0 "original" } } ! { dg-final { cleanup-tree-dump "original" } } -! { dg-final { cleanup-modules "pr26246_1" } } diff --git a/gcc/testsuite/gfortran.dg/pr32222.f90 b/gcc/testsuite/gfortran.dg/pr32222.f90 index 1daac1ef1784..fbe33ed129bb 100644 --- a/gcc/testsuite/gfortran.dg/pr32222.f90 +++ b/gcc/testsuite/gfortran.dg/pr32222.f90 @@ -1,6 +1,5 @@ !PR fortran/32222 ! { dg-do compile } -! { dg-final { cleanup-modules "splinemod" } } module splinemod implicit none diff --git a/gcc/testsuite/gfortran.dg/pr32238.f90 b/gcc/testsuite/gfortran.dg/pr32238.f90 index 2c88b3565614..6af64ca606ad 100644 --- a/gcc/testsuite/gfortran.dg/pr32238.f90 +++ b/gcc/testsuite/gfortran.dg/pr32238.f90 @@ -1,6 +1,5 @@ !PR fortran/32238 ! { dg-do compile } -! { dg-final { cleanup-modules "bug_test" } } module bug_test diff --git a/gcc/testsuite/gfortran.dg/pr32242.f90 b/gcc/testsuite/gfortran.dg/pr32242.f90 index 21ecdd1786c0..8699e0050a18 100644 --- a/gcc/testsuite/gfortran.dg/pr32242.f90 +++ b/gcc/testsuite/gfortran.dg/pr32242.f90 @@ -1,7 +1,6 @@ !PR fortran/32242 ! { dg-do compile } ! { dg-options "-Wreturn-type" } -! { dg-final { cleanup-modules "kahan_sum" } } MODULE kahan_sum INTEGER, PARAMETER :: dp=KIND(0.0D0) diff --git a/gcc/testsuite/gfortran.dg/pr32535.f90 b/gcc/testsuite/gfortran.dg/pr32535.f90 index 43ea48e04cb2..e16882103daf 100644 --- a/gcc/testsuite/gfortran.dg/pr32535.f90 +++ b/gcc/testsuite/gfortran.dg/pr32535.f90 @@ -22,5 +22,3 @@ contains end subroutine subsub end subroutine sub end module mo - -! { dg-final { cleanup-modules "mo" } } diff --git a/gcc/testsuite/gfortran.dg/pr32601.f03 b/gcc/testsuite/gfortran.dg/pr32601.f03 index 90fa6b3f4127..6fa275e0e522 100644 --- a/gcc/testsuite/gfortran.dg/pr32601.f03 +++ b/gcc/testsuite/gfortran.dg/pr32601.f03 @@ -25,4 +25,3 @@ print *, t ! { dg-error "has PRIVATE components" } print *, c_loc(get_ptr()) ! { dg-error "has PRIVATE components" } end -! { dg-final { cleanup-modules "pr32601" } } diff --git a/gcc/testsuite/gfortran.dg/pr32738.f90 b/gcc/testsuite/gfortran.dg/pr32738.f90 index bee6f184cc42..3c413f10cb15 100644 --- a/gcc/testsuite/gfortran.dg/pr32738.f90 +++ b/gcc/testsuite/gfortran.dg/pr32738.f90 @@ -42,5 +42,3 @@ program example implicit none print *, tree_size(1) end program example - -! { dg-final { cleanup-modules "cluster_definition cluster_tree" } } diff --git a/gcc/testsuite/gfortran.dg/pr32921.f b/gcc/testsuite/gfortran.dg/pr32921.f index e809d6ced270..45ea6479b8ad 100644 --- a/gcc/testsuite/gfortran.dg/pr32921.f +++ b/gcc/testsuite/gfortran.dg/pr32921.f @@ -47,4 +47,3 @@ END ! { dg-final { scan-tree-dump-times "stride" 4 "lim1" } } ! { dg-final { cleanup-tree-dump "lim1" } } -! { dg-final { cleanup-modules "les3d_data" } } diff --git a/gcc/testsuite/gfortran.dg/pr33646.f90 b/gcc/testsuite/gfortran.dg/pr33646.f90 index 15186b615fc4..3b5662e4ca57 100644 --- a/gcc/testsuite/gfortran.dg/pr33646.f90 +++ b/gcc/testsuite/gfortran.dg/pr33646.f90 @@ -55,5 +55,3 @@ contains call create_(self) end subroutine end - -! { dg-final { cleanup-modules "bar_module foo_module" } } diff --git a/gcc/testsuite/gfortran.dg/pr33794.f90 b/gcc/testsuite/gfortran.dg/pr33794.f90 index 740f1ea1d346..affad5eb66e7 100644 --- a/gcc/testsuite/gfortran.dg/pr33794.f90 +++ b/gcc/testsuite/gfortran.dg/pr33794.f90 @@ -46,5 +46,3 @@ program test call self_ind_cir_coil (r, l, turns, mu, self_l) end program test - -! { dg-final { cleanup-modules "scc_m" } } diff --git a/gcc/testsuite/gfortran.dg/pr37286.f90 b/gcc/testsuite/gfortran.dg/pr37286.f90 index 75c6814415c6..607fca496e57 100644 --- a/gcc/testsuite/gfortran.dg/pr37286.f90 +++ b/gcc/testsuite/gfortran.dg/pr37286.f90 @@ -54,5 +54,3 @@ contains end function gn_monte_rand end module general_rand - -! { dg-final { cleanup-modules "general_rand" } } diff --git a/gcc/testsuite/gfortran.dg/pr37287-1.f90 b/gcc/testsuite/gfortran.dg/pr37287-1.f90 index 629966fe9f64..c2d42e6de0f4 100644 --- a/gcc/testsuite/gfortran.dg/pr37287-1.f90 +++ b/gcc/testsuite/gfortran.dg/pr37287-1.f90 @@ -12,5 +12,3 @@ contains end subroutine set_null end module pr37287_1 end -! { dg-final { cleanup-modules "pr37287_1" } } -! { dg-final { cleanup-modules "pr37287_2" } } diff --git a/gcc/testsuite/gfortran.dg/pr37287-2.F90 b/gcc/testsuite/gfortran.dg/pr37287-2.F90 index 330ab42cd317..576b645d077d 100644 --- a/gcc/testsuite/gfortran.dg/pr37287-2.F90 +++ b/gcc/testsuite/gfortran.dg/pr37287-2.F90 @@ -7,4 +7,3 @@ module pr37287_2 #endif implicit none end module pr37287_2 -! { dg-final { cleanup-modules "pr37287_2" } } diff --git a/gcc/testsuite/gfortran.dg/pr41347.f90 b/gcc/testsuite/gfortran.dg/pr41347.f90 index e8ceef5f7d98..ae48857d5073 100644 --- a/gcc/testsuite/gfortran.dg/pr41347.f90 +++ b/gcc/testsuite/gfortran.dg/pr41347.f90 @@ -30,4 +30,3 @@ module hsl_ma41_m end subroutine prininfo end module hsl_ma41_m -! { dg-final { cleanup-modules "hsl_ma41_m" } } diff --git a/gcc/testsuite/gfortran.dg/pr41928.f90 b/gcc/testsuite/gfortran.dg/pr41928.f90 index 3d0c25cdb2ec..1438b0c122d3 100644 --- a/gcc/testsuite/gfortran.dg/pr41928.f90 +++ b/gcc/testsuite/gfortran.dg/pr41928.f90 @@ -261,4 +261,3 @@ CONTAINS END DO END SUBROUTINE diff_momop END MODULE ai_moments -! { dg-final { cleanup-modules "kinds ai_moments" } } diff --git a/gcc/testsuite/gfortran.dg/pr42051.f03 b/gcc/testsuite/gfortran.dg/pr42051.f03 index 308c1e7229f7..7a5be635f107 100644 --- a/gcc/testsuite/gfortran.dg/pr42051.f03 +++ b/gcc/testsuite/gfortran.dg/pr42051.f03 @@ -32,5 +32,3 @@ contains end module end - -! { dg-final { cleanup-modules "grid_module field_module" } } diff --git a/gcc/testsuite/gfortran.dg/pr42119.f90 b/gcc/testsuite/gfortran.dg/pr42119.f90 index 962181d2f407..f848e9e9f60e 100644 --- a/gcc/testsuite/gfortran.dg/pr42119.f90 +++ b/gcc/testsuite/gfortran.dg/pr42119.f90 @@ -22,4 +22,3 @@ program Main call Check(C_FUNLOC(Callback)) end program Main -! { dg-final { cleanup-modules "test" } } diff --git a/gcc/testsuite/gfortran.dg/pr42166.f90 b/gcc/testsuite/gfortran.dg/pr42166.f90 index 910a08c36fcf..e29867edae57 100644 --- a/gcc/testsuite/gfortran.dg/pr42166.f90 +++ b/gcc/testsuite/gfortran.dg/pr42166.f90 @@ -17,5 +17,3 @@ CONTAINS END DO END SUBROUTINE newuob END MODULE powell - -! { dg-final { cleanup-modules "powell" } } diff --git a/gcc/testsuite/gfortran.dg/pr43505.f90 b/gcc/testsuite/gfortran.dg/pr43505.f90 index b912c9ff0dd8..1f6b0b272241 100644 --- a/gcc/testsuite/gfortran.dg/pr43505.f90 +++ b/gcc/testsuite/gfortran.dg/pr43505.f90 @@ -39,6 +39,3 @@ end subroutine END PROGRAM TEST -! { dg-final { cleanup-modules "main1" } } - - diff --git a/gcc/testsuite/gfortran.dg/pr43793.f90 b/gcc/testsuite/gfortran.dg/pr43793.f90 index c30f8422bea0..17d5bbe69401 100644 --- a/gcc/testsuite/gfortran.dg/pr43793.f90 +++ b/gcc/testsuite/gfortran.dg/pr43793.f90 @@ -20,4 +20,3 @@ contains end if end subroutine sparse_alltoall end module fft_tools -! { dg-final { cleanup-modules "fft_tools" } } diff --git a/gcc/testsuite/gfortran.dg/pr43866.f90 b/gcc/testsuite/gfortran.dg/pr43866.f90 index abfdaa1557f1..4cfec0feb1ff 100644 --- a/gcc/testsuite/gfortran.dg/pr43866.f90 +++ b/gcc/testsuite/gfortran.dg/pr43866.f90 @@ -40,5 +40,3 @@ END MODULE PR43866 Q%B=0 CALL FOO (Q,N,N,.FALSE.) END - -! { dg-final { cleanup-modules "pr43866" } } diff --git a/gcc/testsuite/gfortran.dg/pr43984.f90 b/gcc/testsuite/gfortran.dg/pr43984.f90 index a4f151d3d973..40c81b84c6c2 100644 --- a/gcc/testsuite/gfortran.dg/pr43984.f90 +++ b/gcc/testsuite/gfortran.dg/pr43984.f90 @@ -54,4 +54,3 @@ end ! { dg-final { scan-tree-dump-times "= iyz.data" 3 "pre" } } ! { dg-final { cleanup-tree-dump "pre" } } -! { dg-final { cleanup-modules "test" } } diff --git a/gcc/testsuite/gfortran.dg/pr50875.f90 b/gcc/testsuite/gfortran.dg/pr50875.f90 index 6b4476c14e4b..0c71080f0b25 100644 --- a/gcc/testsuite/gfortran.dg/pr50875.f90 +++ b/gcc/testsuite/gfortran.dg/pr50875.f90 @@ -35,5 +35,3 @@ contains end subroutine routine_A end module test - -! { dg-final { cleanup-modules "test" } } diff --git a/gcc/testsuite/gfortran.dg/present_1.f90 b/gcc/testsuite/gfortran.dg/present_1.f90 index a3850c44d91e..22e6c0a5a278 100644 --- a/gcc/testsuite/gfortran.dg/present_1.f90 +++ b/gcc/testsuite/gfortran.dg/present_1.f90 @@ -17,4 +17,3 @@ END SUBROUTINE S1 END MODULE END -! { dg-final { cleanup-modules "m1" } } diff --git a/gcc/testsuite/gfortran.dg/private_type_1.f90 b/gcc/testsuite/gfortran.dg/private_type_1.f90 index 96b2eb4c8be9..0f0f8d25c443 100644 --- a/gcc/testsuite/gfortran.dg/private_type_1.f90 +++ b/gcc/testsuite/gfortran.dg/private_type_1.f90 @@ -17,5 +17,3 @@ contains real :: local_array(4) end subroutine dummysub end module modboom - -! { dg-final { cleanup-modules "modboom" } } diff --git a/gcc/testsuite/gfortran.dg/private_type_10.f90 b/gcc/testsuite/gfortran.dg/private_type_10.f90 index 561cfb7fd242..b091db4f7f13 100644 --- a/gcc/testsuite/gfortran.dg/private_type_10.f90 +++ b/gcc/testsuite/gfortran.dg/private_type_10.f90 @@ -30,5 +30,3 @@ module demo2 type(myint), save :: foo2 ! { dg-error "of PRIVATE derived type" } public :: foo2 end module demo2 - -! { dg-final { cleanup-modules "demo" } } diff --git a/gcc/testsuite/gfortran.dg/private_type_11.f90 b/gcc/testsuite/gfortran.dg/private_type_11.f90 index 57c22dd52325..53d5f4c705c0 100644 --- a/gcc/testsuite/gfortran.dg/private_type_11.f90 +++ b/gcc/testsuite/gfortran.dg/private_type_11.f90 @@ -21,4 +21,3 @@ CONTAINS TYPE(T1) FUNCTION F2() END FUNCTION F2 END MODULE M1 -! { dg-final { cleanup-modules "m1" } } diff --git a/gcc/testsuite/gfortran.dg/private_type_12.f90 b/gcc/testsuite/gfortran.dg/private_type_12.f90 index 5bebcf030b7f..c9867bcf87ba 100644 --- a/gcc/testsuite/gfortran.dg/private_type_12.f90 +++ b/gcc/testsuite/gfortran.dg/private_type_12.f90 @@ -21,4 +21,3 @@ CONTAINS TYPE(T1) FUNCTION F2() ! { dg-error "Fortran 2003: PUBLIC variable 'f2'" } END FUNCTION F2 END MODULE M1 -! { dg-final { cleanup-modules "m1" } } diff --git a/gcc/testsuite/gfortran.dg/private_type_13.f90 b/gcc/testsuite/gfortran.dg/private_type_13.f90 index 77c41a44f12e..598e06281bf7 100644 --- a/gcc/testsuite/gfortran.dg/private_type_13.f90 +++ b/gcc/testsuite/gfortran.dg/private_type_13.f90 @@ -29,4 +29,3 @@ module m end subroutine end module -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/private_type_14.f90 b/gcc/testsuite/gfortran.dg/private_type_14.f90 index 6c90b86411a7..ac31721b8a5f 100644 --- a/gcc/testsuite/gfortran.dg/private_type_14.f90 +++ b/gcc/testsuite/gfortran.dg/private_type_14.f90 @@ -39,5 +39,3 @@ program test_ext end do write(*, *) 'OK' end program - -! { dg-final { cleanup-modules "type_ext" } } diff --git a/gcc/testsuite/gfortran.dg/private_type_2.f90 b/gcc/testsuite/gfortran.dg/private_type_2.f90 index f41e151b4cfd..3850ad1a9c8d 100644 --- a/gcc/testsuite/gfortran.dg/private_type_2.f90 +++ b/gcc/testsuite/gfortran.dg/private_type_2.f90 @@ -23,5 +23,3 @@ MODULE TEST public all_type, any_type END MODULE END - -! { dg-final { cleanup-modules "test" } } diff --git a/gcc/testsuite/gfortran.dg/private_type_3.f90 b/gcc/testsuite/gfortran.dg/private_type_3.f90 index dea35818ea35..89ffa638d00a 100644 --- a/gcc/testsuite/gfortran.dg/private_type_3.f90 +++ b/gcc/testsuite/gfortran.dg/private_type_3.f90 @@ -30,5 +30,3 @@ module c arg_t%c = 42 end subroutine d end module c - -! { dg-final { cleanup-modules "a c" } } diff --git a/gcc/testsuite/gfortran.dg/private_type_4.f90 b/gcc/testsuite/gfortran.dg/private_type_4.f90 index 42303ca53cca..95b8fe304172 100644 --- a/gcc/testsuite/gfortran.dg/private_type_4.f90 +++ b/gcc/testsuite/gfortran.dg/private_type_4.f90 @@ -18,5 +18,3 @@ contains end function end module - -! { dg-final { cleanup-modules "m1" } } diff --git a/gcc/testsuite/gfortran.dg/private_type_5.f90 b/gcc/testsuite/gfortran.dg/private_type_5.f90 index 0fcf00e53a59..a6a417f176c2 100644 --- a/gcc/testsuite/gfortran.dg/private_type_5.f90 +++ b/gcc/testsuite/gfortran.dg/private_type_5.f90 @@ -22,4 +22,3 @@ contains end subroutine init end subroutine sub end module test -! { dg-final { cleanup-modules "test" } } diff --git a/gcc/testsuite/gfortran.dg/private_type_6.f90 b/gcc/testsuite/gfortran.dg/private_type_6.f90 index 4af3f704f98c..e980cb969077 100644 --- a/gcc/testsuite/gfortran.dg/private_type_6.f90 +++ b/gcc/testsuite/gfortran.dg/private_type_6.f90 @@ -22,4 +22,3 @@ program foo_test foo2 = bartype(1,2) ! { dg-error "is a PRIVATE component" } foo2%dummy2 = 5 ! { dg-error "is a PRIVATE component" } end program foo_test -! { dg-final { cleanup-modules "foomod" } } diff --git a/gcc/testsuite/gfortran.dg/private_type_7.f90 b/gcc/testsuite/gfortran.dg/private_type_7.f90 index b9ad8fab7ed4..c44917259c20 100644 --- a/gcc/testsuite/gfortran.dg/private_type_7.f90 +++ b/gcc/testsuite/gfortran.dg/private_type_7.f90 @@ -32,4 +32,3 @@ program testit k = foo(i) print *, "in the main:", k end program testit -! { dg-final { cleanup-modules "gfcbug68" } } diff --git a/gcc/testsuite/gfortran.dg/private_type_8.f90 b/gcc/testsuite/gfortran.dg/private_type_8.f90 index df1609646cfa..111cbb1becf8 100644 --- a/gcc/testsuite/gfortran.dg/private_type_8.f90 +++ b/gcc/testsuite/gfortran.dg/private_type_8.f90 @@ -17,5 +17,3 @@ contains real :: local_array(4) end subroutine dummysub end module modboom - -! { dg-final { cleanup-modules "modboom" } } diff --git a/gcc/testsuite/gfortran.dg/private_type_9.f90 b/gcc/testsuite/gfortran.dg/private_type_9.f90 index 3ca2fd5fb0f0..078041ae0bec 100644 --- a/gcc/testsuite/gfortran.dg/private_type_9.f90 +++ b/gcc/testsuite/gfortran.dg/private_type_9.f90 @@ -39,4 +39,3 @@ module m4 end module m4 end -! { dg-final { cleanup-modules "m1 m2 m3 m4" } } diff --git a/gcc/testsuite/gfortran.dg/proc_assign_1.f90 b/gcc/testsuite/gfortran.dg/proc_assign_1.f90 index e85df7635deb..d6a8783919e5 100644 --- a/gcc/testsuite/gfortran.dg/proc_assign_1.f90 +++ b/gcc/testsuite/gfortran.dg/proc_assign_1.f90 @@ -77,4 +77,3 @@ contains y = 2 ! OK - function result end function y end -! { dg-final { cleanup-modules "simple simpler" } } diff --git a/gcc/testsuite/gfortran.dg/proc_assign_2.f90 b/gcc/testsuite/gfortran.dg/proc_assign_2.f90 index 8f313c58fa31..4c343bf53c5a 100644 --- a/gcc/testsuite/gfortran.dg/proc_assign_2.f90 +++ b/gcc/testsuite/gfortran.dg/proc_assign_2.f90 @@ -18,4 +18,3 @@ CONTAINS END FUNCTION END FUNCTION END MODULE -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/proc_decl_10.f90 b/gcc/testsuite/gfortran.dg/proc_decl_10.f90 index 88fd6d8a793a..ff725c3ec0cb 100644 --- a/gcc/testsuite/gfortran.dg/proc_decl_10.f90 +++ b/gcc/testsuite/gfortran.dg/proc_decl_10.f90 @@ -28,5 +28,3 @@ procedure(cos) :: my2 ! { dg-error "Cannot change attributes" } procedure(dprod) :: my3 ! { dg-error "Cannot change attributes" } end program test - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/proc_decl_12.f90 b/gcc/testsuite/gfortran.dg/proc_decl_12.f90 index 092c24d36141..37fc4a4e420e 100644 --- a/gcc/testsuite/gfortran.dg/proc_decl_12.f90 +++ b/gcc/testsuite/gfortran.dg/proc_decl_12.f90 @@ -23,5 +23,3 @@ contains call f([1,2,3]) end subroutine foo end program test - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/proc_decl_13.f90 b/gcc/testsuite/gfortran.dg/proc_decl_13.f90 index b875376a09d0..1df220b7cf64 100644 --- a/gcc/testsuite/gfortran.dg/proc_decl_13.f90 +++ b/gcc/testsuite/gfortran.dg/proc_decl_13.f90 @@ -40,6 +40,4 @@ contains end interface call f([1,2,3]) ! Works end subroutine foo2 - -! { dg-final { cleanup-modules "m" } } end program test diff --git a/gcc/testsuite/gfortran.dg/proc_decl_17.f90 b/gcc/testsuite/gfortran.dg/proc_decl_17.f90 index 858022a43fab..0daee4668994 100644 --- a/gcc/testsuite/gfortran.dg/proc_decl_17.f90 +++ b/gcc/testsuite/gfortran.dg/proc_decl_17.f90 @@ -64,5 +64,3 @@ my_message = (/'a','b','c','d','e','f'/) call check(foo,i) end program - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/proc_decl_18.f90 b/gcc/testsuite/gfortran.dg/proc_decl_18.f90 index 46493eb9e0ff..15993626cc9e 100644 --- a/gcc/testsuite/gfortran.dg/proc_decl_18.f90 +++ b/gcc/testsuite/gfortran.dg/proc_decl_18.f90 @@ -59,5 +59,3 @@ end p(l) = y(l)*2 end do end function - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/proc_decl_2.f90 b/gcc/testsuite/gfortran.dg/proc_decl_2.f90 index 1cbfe97942ac..a16b4db5f019 100644 --- a/gcc/testsuite/gfortran.dg/proc_decl_2.f90 +++ b/gcc/testsuite/gfortran.dg/proc_decl_2.f90 @@ -146,5 +146,3 @@ function p7(x) integer :: x, p7 p7 = x*(-2) end function - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/proc_decl_20.f90 b/gcc/testsuite/gfortran.dg/proc_decl_20.f90 index 612dac19529e..7afac3369f88 100644 --- a/gcc/testsuite/gfortran.dg/proc_decl_20.f90 +++ b/gcc/testsuite/gfortran.dg/proc_decl_20.f90 @@ -20,5 +20,3 @@ end module other_fun use other_fun procedure(abstract_fun) :: fun end program fptr - -! { dg-final { cleanup-modules "other_fun" } } diff --git a/gcc/testsuite/gfortran.dg/proc_decl_23.f90 b/gcc/testsuite/gfortran.dg/proc_decl_23.f90 index 66cf5fff736e..fa50dc13c86e 100644 --- a/gcc/testsuite/gfortran.dg/proc_decl_23.f90 +++ b/gcc/testsuite/gfortran.dg/proc_decl_23.f90 @@ -41,4 +41,3 @@ end module m_string print *, char1 (["j","k","l"]) end ! { dg-final { cleanup-tree-dump "m_string" } } -! { dg-final { cleanup-modules "m_string" } } diff --git a/gcc/testsuite/gfortran.dg/proc_decl_27.f90 b/gcc/testsuite/gfortran.dg/proc_decl_27.f90 index 30ff4def30da..cb16ecfa2b01 100644 --- a/gcc/testsuite/gfortran.dg/proc_decl_27.f90 +++ b/gcc/testsuite/gfortran.dg/proc_decl_27.f90 @@ -21,5 +21,3 @@ end implicit none procedure(Proc) :: Proc_Get end - -! { dg-final { cleanup-modules "m1 m2" } } diff --git a/gcc/testsuite/gfortran.dg/proc_decl_5.f90 b/gcc/testsuite/gfortran.dg/proc_decl_5.f90 index b327d5c128ca..d2cb04637888 100644 --- a/gcc/testsuite/gfortran.dg/proc_decl_5.f90 +++ b/gcc/testsuite/gfortran.dg/proc_decl_5.f90 @@ -24,5 +24,3 @@ program test implicit none if(x() /= -5) call abort() end program test - -! { dg-final { cleanup-modules "modproc" } } diff --git a/gcc/testsuite/gfortran.dg/proc_decl_7.f90 b/gcc/testsuite/gfortran.dg/proc_decl_7.f90 index c8c2a81c5c6a..829add2ff9b0 100644 --- a/gcc/testsuite/gfortran.dg/proc_decl_7.f90 +++ b/gcc/testsuite/gfortran.dg/proc_decl_7.f90 @@ -18,4 +18,3 @@ implicit none intrinsic cos call sub(cos) ! { dg-error "wrong number of arguments" } end -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/proc_decl_8.f90 b/gcc/testsuite/gfortran.dg/proc_decl_8.f90 index 2d3514ec896c..dce45b426588 100644 --- a/gcc/testsuite/gfortran.dg/proc_decl_8.f90 +++ b/gcc/testsuite/gfortran.dg/proc_decl_8.f90 @@ -22,4 +22,3 @@ EXTERNAL foo ! interface is undefined procedure(cos) :: foo ! { dg-error "Duplicate EXTERNAL attribute specified" } call sub(foo) ! { dg-error "is not a function" } end -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_1.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_1.f90 index fe8e201000e6..b9c0ce6858fd 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_1.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_1.f90 @@ -69,5 +69,3 @@ program procPtrTest if (ptr6()/=6.3) call abort() end program - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_10.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_10.f90 index e673efe4cddf..dfe8ce9f0a59 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_10.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_10.f90 @@ -27,4 +27,3 @@ program myProg call proc4( p ) end program myProg -! { dg-final { cleanup-modules "mymod" } } diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_13.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_13.f90 index 5c66c54e9dbd..989cd66efefd 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_13.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_13.f90 @@ -25,5 +25,3 @@ END MODULE myfortran_binding use myfortran_binding error_handler => error_stop end - -! { dg-final { cleanup-modules "myfortran_binding" } } diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_20.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_20.f90 index 79c9ba8f1ecf..5aead5b5de20 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_20.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_20.f90 @@ -37,6 +37,3 @@ CONTAINS PRINT*, 'sub' END SUBROUTINE s END PROGRAM prog - -! { dg-final { cleanup-modules "m" } } - diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_22.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_22.f90 index 1f13280326c3..69d165e33a80 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_22.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_22.f90 @@ -25,6 +25,3 @@ program bugTest pp2 => returnMat if (sum(pp2(3,2))/=6) call abort() end program bugTest - -! { dg-final { cleanup-modules "bugtestmod" } } - diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_26.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_26.f90 index 044f0a403bd5..8ae027fe8704 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_26.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_26.f90 @@ -27,5 +27,3 @@ program main if (associated(p_fun) .or. associated(p_fun2)) & call abort () end program main - -! { dg-final { cleanup-modules "mod_a" } } diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_27.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_27.f90 index 83f09598110d..1d916de43181 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_27.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_27.f90 @@ -16,5 +16,3 @@ module m end interface procedure(i_f), pointer, protected :: p_f => null() end module m - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_28.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_28.f90 index 8754d8e29820..ce383cf799b2 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_28.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_28.f90 @@ -35,5 +35,3 @@ CONTAINS END SUBROUTINE use_sub END MODULE m - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_29.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_29.f90 index 69f0b0341960..7247c06a9536 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_29.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_29.f90 @@ -25,5 +25,3 @@ contains y = p(x) end function i_g end module m2 - -! { dg-final { cleanup-modules "m1 m2" } } diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_33.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_33.f90 index 803d90e05eaf..973162bf5e06 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_33.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_33.f90 @@ -28,5 +28,3 @@ program start f => my_dcos ! { dg-error "Mismatch in PURE attribute" } write(*,*) f(x) end program start - -! { dg-final { cleanup-modules "funcs" } } \ No newline at end of file diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_34.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_34.f90 index 6226414b8196..fc5df1f298ea 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_34.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_34.f90 @@ -75,5 +75,3 @@ program test_proc_ptr stop end program test_proc_ptr - -! { dg-final { cleanup-modules "examplefuncs" } } diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_36.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_36.f90 index ada5c565872e..7f3525eed29e 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_36.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_36.f90 @@ -44,5 +44,3 @@ end subroutine s subroutine sub2 end subroutine sub2 - -! { dg-final { cleanup-modules "m0" } } diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_8.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_8.f90 index 55ba58daa675..4785383e96a7 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_8.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_8.f90 @@ -41,5 +41,3 @@ contains end subroutine END - -! { dg-final { cleanup-modules "x" } } diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_comp_10.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_comp_10.f90 index 382f4125533b..715d4368a751 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_comp_10.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_comp_10.f90 @@ -26,6 +26,3 @@ type(t) :: obj obj%ppc => pp pp => obj%ppc end - -! { dg-final { cleanup-modules "m" } } - diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_comp_12.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_comp_12.f90 index 41668b817ae7..8c658d8838bc 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_comp_12.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_comp_12.f90 @@ -30,6 +30,3 @@ program bugTest print *,testObj%test(3,3) if (sum(testObj%test(3,3))/=9) call abort() end program bugTest - -! { dg-final { cleanup-modules "bugtestmod" } } - diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_comp_15.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_comp_15.f90 index 9f15d14dbe4b..37f3a7ae4876 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_comp_15.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_comp_15.f90 @@ -23,6 +23,3 @@ use m str = x%ptr() if (str/='abcde') call abort() end - -! { dg-final { cleanup-modules "m" } } - diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_comp_16.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_comp_16.f90 index e6b77a22f023..ff5634b4e8d0 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_comp_16.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_comp_16.f90 @@ -25,6 +25,3 @@ use m str = x%ptr(3) if (str/='abc') call abort() end - -! { dg-final { cleanup-modules "m" } } - diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_comp_17.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_comp_17.f90 index cfe498b0ecab..6a9f32fdebd8 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_comp_17.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_comp_17.f90 @@ -27,6 +27,3 @@ use m str = 'fghij' if (strptr/='fghij') call abort() end - -! { dg-final { cleanup-modules "m" } } - diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_comp_22.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_comp_22.f90 index b82564ff4ca8..ac3982e5883d 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_comp_22.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_comp_22.f90 @@ -28,4 +28,3 @@ PROGRAM main arr%myproc => myproc ! { dg-error "must not have the POINTER attribute" } END PROGRAM main -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_comp_23.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_comp_23.f90 index 8b1c6912d27b..d91851e82499 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_comp_23.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_comp_23.f90 @@ -70,4 +70,3 @@ print *, p(nr=3,x=(/0.1,0.1/)) print *, funcp%p(nr=3,x=(/0.1,0.1/)) end program t -! { dg-final { cleanup-modules "poisson_functions_m element_defs_m" } } diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_comp_31.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_comp_31.f90 index 6a5d8c967e20..e0e528be28b0 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_comp_31.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_comp_31.f90 @@ -18,5 +18,3 @@ program test_objects type(rectangle) :: rect write(*,*) rect ! { dg-error "cannot have procedure pointer components" } end program - -! { dg-final { cleanup-modules "proc_pointers" } } diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_comp_32.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_comp_32.f90 index eda972a45483..c1d01c527122 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_comp_32.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_comp_32.f90 @@ -33,5 +33,3 @@ use m type(rectangle) :: rect rect%get_special_area => get_my_area ! { dg-error "Interface mismatch in procedure pointer assignment" } end - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_comp_33.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_comp_33.f90 index 1bb863d3a97d..b6a31fe3a0b2 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_comp_33.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_comp_33.f90 @@ -66,6 +66,3 @@ contains end function get2 end - - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_comp_4.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_comp_4.f90 index b904a2f86aaf..be36fda41038 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_comp_4.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_comp_4.f90 @@ -115,6 +115,3 @@ contains end function var_list_get_var_ptr end - -! { dg-final { cleanup-modules "expressions process_libraries hard_interactions" } } - diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_comp_6.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_comp_6.f90 index f0dcf4ccf01d..12aaf7951b8f 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_comp_6.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_comp_6.f90 @@ -59,6 +59,3 @@ program main if (calls/=2) call abort end program main - -! { dg-final { cleanup-modules "proc_component_example" } } - diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_comp_7.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_comp_7.f90 index 860c2dd9b811..48fd5219e4a3 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_comp_7.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_comp_7.f90 @@ -35,6 +35,3 @@ type(public_t) :: x integer :: j j = x%ppc() end - -! { dg-final { cleanup-modules "m" } } - diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_comp_pass_1.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_comp_pass_1.f90 index 4513083ac5d4..0798a7b16f85 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_comp_pass_1.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_comp_pass_1.f90 @@ -43,6 +43,3 @@ program Test_03 if (m%i/=6) call abort() end program Test_03 - -! { dg-final { cleanup-modules "mymod" } } - diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_comp_pass_2.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_comp_pass_2.f90 index 03770ce3ff8f..dc5253dd6d06 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_comp_pass_2.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_comp_pass_2.f90 @@ -43,6 +43,3 @@ program main call x%proc (output_unit) end program main - -! { dg-final { cleanup-modules "passed_object_example" } } - diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_comp_pass_4.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_comp_pass_4.f90 index 0a28b5340b33..b0e7a772723d 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_comp_pass_4.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_comp_pass_4.f90 @@ -70,6 +70,3 @@ contains end function end module m - -! { dg-final { cleanup-modules "m" } } - diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_comp_pass_5.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_comp_pass_5.f90 index 216a554f1104..70a99f9211d2 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_comp_pass_5.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_comp_pass_5.f90 @@ -34,6 +34,3 @@ call t1%foo() call t2%foo() call t2%foo(t1) end - -! { dg-final { cleanup-modules "m" } } - diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_comp_pass_6.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_comp_pass_6.f90 index 4382a3bc2b45..b9ce92daecd9 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_comp_pass_6.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_comp_pass_6.f90 @@ -31,5 +31,3 @@ PROGRAM ProgA CALL arr(i)%Proc(ierr) END DO END PROGRAM ProgA - -! { dg-final { cleanup-modules "moda" } } diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_comp_pass_7.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_comp_pass_7.f90 index a15018db3450..9c960dda21e2 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_comp_pass_7.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_comp_pass_7.f90 @@ -61,5 +61,3 @@ program main call obj%base_t%write_procptr ! { dg-error "is of ABSTRACT type" } end program main - -! { dg-final { cleanup-modules "types" } } diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_result_1.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_result_1.f90 index df830d3b1fcc..a7ea21821d71 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_result_1.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_result_1.f90 @@ -178,6 +178,3 @@ contains end function end - -! { dg-final { cleanup-modules "mo" } } - diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_result_2.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_result_2.f90 index 362a1f7f8485..f5a4fd221ed0 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_result_2.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_result_2.f90 @@ -57,6 +57,3 @@ contains end function end - -! { dg-final { cleanup-modules "proc_ptr_15" } } - diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_result_3.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_result_3.f90 index a84ff2420bab..6e2e5244e919 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_result_3.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_result_3.f90 @@ -51,6 +51,3 @@ recursive subroutine my_sub(j) j = j*3 call set_sub(my_sub) end subroutine my_sub - -! { dg-final { cleanup-modules "store_subroutine" } } - diff --git a/gcc/testsuite/gfortran.dg/proc_ptr_result_6.f90 b/gcc/testsuite/gfortran.dg/proc_ptr_result_6.f90 index c9e1a8b067a0..9d625afb7a61 100644 --- a/gcc/testsuite/gfortran.dg/proc_ptr_result_6.f90 +++ b/gcc/testsuite/gfortran.dg/proc_ptr_result_6.f90 @@ -46,6 +46,3 @@ contains getPtr2 => func end function end program test - -! { dg-final { cleanup-modules "m" } } - diff --git a/gcc/testsuite/gfortran.dg/procedure_lvalue.f90 b/gcc/testsuite/gfortran.dg/procedure_lvalue.f90 index 741dc8c34a3f..915f75e810b4 100644 --- a/gcc/testsuite/gfortran.dg/procedure_lvalue.f90 +++ b/gcc/testsuite/gfortran.dg/procedure_lvalue.f90 @@ -17,5 +17,3 @@ subroutine r b = 1. ! { dg-error "is not a variable" } y = a(1.) end subroutine r - -! { dg-final { cleanup-modules "t" } } diff --git a/gcc/testsuite/gfortran.dg/protected_1.f90 b/gcc/testsuite/gfortran.dg/protected_1.f90 index fbc30e8c6dc4..0805e98664f4 100644 --- a/gcc/testsuite/gfortran.dg/protected_1.f90 +++ b/gcc/testsuite/gfortran.dg/protected_1.f90 @@ -57,5 +57,3 @@ contains if(a /= 44 .or. ap /= 79 .or. at /= 4) call abort() end subroutine end program main - -! { dg-final { cleanup-modules "protmod" } } diff --git a/gcc/testsuite/gfortran.dg/protected_2.f90 b/gcc/testsuite/gfortran.dg/protected_2.f90 index dcdce51c86e6..c00222d08b28 100644 --- a/gcc/testsuite/gfortran.dg/protected_2.f90 +++ b/gcc/testsuite/gfortran.dg/protected_2.f90 @@ -51,5 +51,3 @@ contains if(a /= 44 .or. ap /= 79 .or. at /= 4) call abort() end subroutine end program main - -! { dg-final { cleanup-modules "protmod" } } diff --git a/gcc/testsuite/gfortran.dg/protected_4.f90 b/gcc/testsuite/gfortran.dg/protected_4.f90 index 7f0e49f09a48..2834680a9889 100644 --- a/gcc/testsuite/gfortran.dg/protected_4.f90 +++ b/gcc/testsuite/gfortran.dg/protected_4.f90 @@ -54,5 +54,3 @@ module test real :: a protected :: test ! { dg-error "MODULE attribute conflicts with PROTECTED" } end module test - -! { dg-final { cleanup-modules "protmod test" } } diff --git a/gcc/testsuite/gfortran.dg/protected_5.f90 b/gcc/testsuite/gfortran.dg/protected_5.f90 index 85046c3cb9ae..4901b82143d6 100644 --- a/gcc/testsuite/gfortran.dg/protected_5.f90 +++ b/gcc/testsuite/gfortran.dg/protected_5.f90 @@ -53,5 +53,3 @@ program main nullify(t%p) ! { dg-error "pointer association context" } allocate(t%array(15))! { dg-error "variable definition context" } end program main - -! { dg-final { cleanup-modules "good1 good2 bad1 bad2" } } diff --git a/gcc/testsuite/gfortran.dg/protected_6.f90 b/gcc/testsuite/gfortran.dg/protected_6.f90 index e7f3e4e93374..8e85bbfe06d6 100644 --- a/gcc/testsuite/gfortran.dg/protected_6.f90 +++ b/gcc/testsuite/gfortran.dg/protected_6.f90 @@ -47,5 +47,3 @@ contains real, protected :: b ! { dg-error "only allowed in specification part of a module" } end subroutine bar end module prot2 - -! { dg-final { cleanup-modules "protmod" } } diff --git a/gcc/testsuite/gfortran.dg/protected_7.f90 b/gcc/testsuite/gfortran.dg/protected_7.f90 index abdc9592aaf3..0f84da54886a 100644 --- a/gcc/testsuite/gfortran.dg/protected_7.f90 +++ b/gcc/testsuite/gfortran.dg/protected_7.f90 @@ -18,5 +18,3 @@ program p unprotected_pointer => protected_target ! { dg-error "target has PROTECTED attribute" } unprotected_pointer => protected_pointer ! OK end program p - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/protected_8.f90 b/gcc/testsuite/gfortran.dg/protected_8.f90 index aaa34a68f9bf..7e02044720de 100644 --- a/gcc/testsuite/gfortran.dg/protected_8.f90 +++ b/gcc/testsuite/gfortran.dg/protected_8.f90 @@ -46,5 +46,3 @@ PROGRAM test b%j = 5 ! OK 5 END PROGRAM test - -! { dg-final { cleanup-modules "amod" } } diff --git a/gcc/testsuite/gfortran.dg/public_private_module.f90 b/gcc/testsuite/gfortran.dg/public_private_module.f90 index 48e78b60cfa7..709c01e8d8cf 100644 --- a/gcc/testsuite/gfortran.dg/public_private_module.f90 +++ b/gcc/testsuite/gfortran.dg/public_private_module.f90 @@ -16,4 +16,3 @@ module d implicit none private a ! { dg-error "attribute applied to" } end module d -! { dg-final { cleanup-modules "a" } } diff --git a/gcc/testsuite/gfortran.dg/pure_byref_3.f90 b/gcc/testsuite/gfortran.dg/pure_byref_3.f90 index a9d860bf0414..cb2644ff8982 100644 --- a/gcc/testsuite/gfortran.dg/pure_byref_3.f90 +++ b/gcc/testsuite/gfortran.dg/pure_byref_3.f90 @@ -31,5 +31,3 @@ program pure_byref_3 a = hoj() if (.not. all(a == (/1, 2, 3/))) call abort() end program pure_byref_3 - -! { dg-final { cleanup-modules "huj_mod" } } diff --git a/gcc/testsuite/gfortran.dg/pure_formal_proc_2.f90 b/gcc/testsuite/gfortran.dg/pure_formal_proc_2.f90 index 687e43e93fda..c683a6c51f9b 100644 --- a/gcc/testsuite/gfortran.dg/pure_formal_proc_2.f90 +++ b/gcc/testsuite/gfortran.dg/pure_formal_proc_2.f90 @@ -45,4 +45,3 @@ program Test deallocate(pT1) end program Test -! { dg-final { cleanup-modules "testpure" } } diff --git a/gcc/testsuite/gfortran.dg/pure_initializer_2.f90 b/gcc/testsuite/gfortran.dg/pure_initializer_2.f90 index 4fd2556efca6..afb00c661ae2 100644 --- a/gcc/testsuite/gfortran.dg/pure_initializer_2.f90 +++ b/gcc/testsuite/gfortran.dg/pure_initializer_2.f90 @@ -43,4 +43,3 @@ pure function test() integer :: test test = p end function test -! { dg-final { cleanup-modules "mod_xyz mod_xyz2 mod_xyz3" } } diff --git a/gcc/testsuite/gfortran.dg/realloc_on_assign_13.f90 b/gcc/testsuite/gfortran.dg/realloc_on_assign_13.f90 index 9661d724f5b6..bc7395a9ba78 100644 --- a/gcc/testsuite/gfortran.dg/realloc_on_assign_13.f90 +++ b/gcc/testsuite/gfortran.dg/realloc_on_assign_13.f90 @@ -16,5 +16,3 @@ contains reduced = pack (array, mask) end function reduced end module cascades -! { dg-final { cleanup-modules "cascades" } } - diff --git a/gcc/testsuite/gfortran.dg/realloc_on_assign_4.f03 b/gcc/testsuite/gfortran.dg/realloc_on_assign_4.f03 index 682a81c962a6..8e7d49b0fa88 100644 --- a/gcc/testsuite/gfortran.dg/realloc_on_assign_4.f03 +++ b/gcc/testsuite/gfortran.dg/realloc_on_assign_4.f03 @@ -46,6 +46,3 @@ contains bar = carg(1:12) end function end - -! { dg-final { cleanup-modules "m" } } - diff --git a/gcc/testsuite/gfortran.dg/realloc_on_assign_6.f03 b/gcc/testsuite/gfortran.dg/realloc_on_assign_6.f03 index 7c170ebce271..3c96c73a7438 100644 --- a/gcc/testsuite/gfortran.dg/realloc_on_assign_6.f03 +++ b/gcc/testsuite/gfortran.dg/realloc_on_assign_6.f03 @@ -124,6 +124,3 @@ do k = 1,size(some_type_to_save) end do end subroutine print_after_transfer -! { dg-final { cleanup-modules "m gf33" } } -! { dg-final { cleanup-modules "custom_type custom_interfaces" } } -! { dg-final { cleanup-modules "store_data_test" } } diff --git a/gcc/testsuite/gfortran.dg/realloc_on_assign_9.f90 b/gcc/testsuite/gfortran.dg/realloc_on_assign_9.f90 index d03db3244b35..69f1ecc02159 100644 --- a/gcc/testsuite/gfortran.dg/realloc_on_assign_9.f90 +++ b/gcc/testsuite/gfortran.dg/realloc_on_assign_9.f90 @@ -30,5 +30,3 @@ program main july4 = new_show(boom=fireworks) end program - -! { dg-final { cleanup-modules "soop_stars_class" } } diff --git a/gcc/testsuite/gfortran.dg/recursive_check_12.f90 b/gcc/testsuite/gfortran.dg/recursive_check_12.f90 index 22eaf7d0f282..ec85c11ed8cf 100644 --- a/gcc/testsuite/gfortran.dg/recursive_check_12.f90 +++ b/gcc/testsuite/gfortran.dg/recursive_check_12.f90 @@ -26,4 +26,3 @@ program test call f(.false.) call f(.false.) end program test -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/recursive_check_13.f90 b/gcc/testsuite/gfortran.dg/recursive_check_13.f90 index ed222a322ec5..05d0c2fac54e 100644 --- a/gcc/testsuite/gfortran.dg/recursive_check_13.f90 +++ b/gcc/testsuite/gfortran.dg/recursive_check_13.f90 @@ -29,4 +29,3 @@ program test call f(.false.) call f(.true.) end program test -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/recursive_check_3.f90 b/gcc/testsuite/gfortran.dg/recursive_check_3.f90 index 76782861087f..ec358cb12c05 100644 --- a/gcc/testsuite/gfortran.dg/recursive_check_3.f90 +++ b/gcc/testsuite/gfortran.dg/recursive_check_3.f90 @@ -20,4 +20,3 @@ 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-final { cleanup-modules "m1 m2 m3" } } diff --git a/gcc/testsuite/gfortran.dg/recursive_check_4.f03 b/gcc/testsuite/gfortran.dg/recursive_check_4.f03 index d33e53555ca1..ece42ca2312f 100644 --- a/gcc/testsuite/gfortran.dg/recursive_check_4.f03 +++ b/gcc/testsuite/gfortran.dg/recursive_check_4.f03 @@ -32,5 +32,3 @@ CONTAINS END FUNCTION func END MODULE m - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/recursive_check_5.f03 b/gcc/testsuite/gfortran.dg/recursive_check_5.f03 index 4014986b3b54..4fe84106a282 100644 --- a/gcc/testsuite/gfortran.dg/recursive_check_5.f03 +++ b/gcc/testsuite/gfortran.dg/recursive_check_5.f03 @@ -23,5 +23,3 @@ CONTAINS END FUNCTION func END MODULE m - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/recursive_check_6.f03 b/gcc/testsuite/gfortran.dg/recursive_check_6.f03 index 478539e6a498..9414f587b901 100644 --- a/gcc/testsuite/gfortran.dg/recursive_check_6.f03 +++ b/gcc/testsuite/gfortran.dg/recursive_check_6.f03 @@ -62,5 +62,3 @@ CONTAINS END SUBROUTINE main END MODULE m - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/recursive_reference_2.f90 b/gcc/testsuite/gfortran.dg/recursive_reference_2.f90 index 59df43cdf1ae..265b8701b9b5 100644 --- a/gcc/testsuite/gfortran.dg/recursive_reference_2.f90 +++ b/gcc/testsuite/gfortran.dg/recursive_reference_2.f90 @@ -30,5 +30,3 @@ integer :: ans(5) IF (ANY(TEST(3).NE.(/5,5,5,5,5/))) CALL ABORT() IF (ANY(TEST(6).NE.(/0,0,0,0,0/))) CALL ABORT() END -! { dg-final { cleanup-modules "m1" } } - diff --git a/gcc/testsuite/gfortran.dg/redefined_intrinsic_assignment.f90 b/gcc/testsuite/gfortran.dg/redefined_intrinsic_assignment.f90 index 8eb47e19b811..40a0910b1ed9 100644 --- a/gcc/testsuite/gfortran.dg/redefined_intrinsic_assignment.f90 +++ b/gcc/testsuite/gfortran.dg/redefined_intrinsic_assignment.f90 @@ -16,4 +16,3 @@ CONTAINS I=-J END SUBROUTINE T1 END MODULE M1 -! { dg-final { cleanup-modules "m1" } } diff --git a/gcc/testsuite/gfortran.dg/redefined_intrinsic_assignment_2.f90 b/gcc/testsuite/gfortran.dg/redefined_intrinsic_assignment_2.f90 index ba70902091e8..5e953222ec8c 100644 --- a/gcc/testsuite/gfortran.dg/redefined_intrinsic_assignment_2.f90 +++ b/gcc/testsuite/gfortran.dg/redefined_intrinsic_assignment_2.f90 @@ -64,5 +64,3 @@ contains lhs(:) = rhs(:) end subroutine invalid3 end module test4 - -! { dg-final { cleanup-modules "test1" } } diff --git a/gcc/testsuite/gfortran.dg/reshape_2.f90 b/gcc/testsuite/gfortran.dg/reshape_2.f90 index d28058dddb23..1a85712292db 100644 --- a/gcc/testsuite/gfortran.dg/reshape_2.f90 +++ b/gcc/testsuite/gfortran.dg/reshape_2.f90 @@ -21,4 +21,3 @@ program test if (nxttab(linem, 1) .ne. 6) call abort if (nxttab(linem, nplam) .ne. 132) call abort end program test -! { dg-final { cleanup-modules "splitprms" } } \ No newline at end of file diff --git a/gcc/testsuite/gfortran.dg/reshape_zerosize_3.f90 b/gcc/testsuite/gfortran.dg/reshape_zerosize_3.f90 index 870a76c652ea..de39a306da92 100644 --- a/gcc/testsuite/gfortran.dg/reshape_zerosize_3.f90 +++ b/gcc/testsuite/gfortran.dg/reshape_zerosize_3.f90 @@ -40,4 +40,3 @@ END MODULE M1 USE M1 CALL S2(0) END -! { dg-final { cleanup-modules "m1" } } diff --git a/gcc/testsuite/gfortran.dg/result_in_spec_1.f90 b/gcc/testsuite/gfortran.dg/result_in_spec_1.f90 index cbeb60f2d82e..6189e55919d1 100644 --- a/gcc/testsuite/gfortran.dg/result_in_spec_1.f90 +++ b/gcc/testsuite/gfortran.dg/result_in_spec_1.f90 @@ -49,4 +49,3 @@ pure function f(x) integer f f = 2*x+1 end function f -! { dg-final { cleanup-modules "test1" } } diff --git a/gcc/testsuite/gfortran.dg/result_in_spec_2.f90 b/gcc/testsuite/gfortran.dg/result_in_spec_2.f90 index cffa2300c20d..028e4034a6c8 100644 --- a/gcc/testsuite/gfortran.dg/result_in_spec_2.f90 +++ b/gcc/testsuite/gfortran.dg/result_in_spec_2.f90 @@ -28,4 +28,3 @@ program test if(len (test2()) /= 3) call abort () if(test2() /= '123') call abort () end program test -! { dg-final { cleanup-modules "test1" } } diff --git a/gcc/testsuite/gfortran.dg/result_in_spec_4.f90 b/gcc/testsuite/gfortran.dg/result_in_spec_4.f90 index 3f0e9a37910c..5228b9b84291 100644 --- a/gcc/testsuite/gfortran.dg/result_in_spec_4.f90 +++ b/gcc/testsuite/gfortran.dg/result_in_spec_4.f90 @@ -23,5 +23,3 @@ contains sigma2 = MATMUL(getPhaseMatrix(), sigma2) END SUBROUTINE end module m - -! { dg-final { cleanup-modules "m m2" } } diff --git a/gcc/testsuite/gfortran.dg/same_name_1.f90 b/gcc/testsuite/gfortran.dg/same_name_1.f90 index 5cf13a93bed7..cbeb875e36b3 100644 --- a/gcc/testsuite/gfortran.dg/same_name_1.f90 +++ b/gcc/testsuite/gfortran.dg/same_name_1.f90 @@ -11,5 +11,3 @@ contains subroutine u end subroutine u end module m - -! { dg-final { cleanup-modules "n m" } } diff --git a/gcc/testsuite/gfortran.dg/same_name_2.f90 b/gcc/testsuite/gfortran.dg/same_name_2.f90 index c8da3e1dbbff..463ac8533f8b 100644 --- a/gcc/testsuite/gfortran.dg/same_name_2.f90 +++ b/gcc/testsuite/gfortran.dg/same_name_2.f90 @@ -13,4 +13,3 @@ subroutine aa ! { dg-error "is already defined" } write(*,*) 'BB' end subroutine aa end module -! { dg-final { cleanup-modules "aha" } } diff --git a/gcc/testsuite/gfortran.dg/save_3.f90 b/gcc/testsuite/gfortran.dg/save_3.f90 index ab2ee52685a3..d2deed17e04a 100644 --- a/gcc/testsuite/gfortran.dg/save_3.f90 +++ b/gcc/testsuite/gfortran.dg/save_3.f90 @@ -14,5 +14,3 @@ pure function tell_i() result (answer) answer=i end function tell_i end module g95bug - -! { dg-final { cleanup-modules "g95bug" } } diff --git a/gcc/testsuite/gfortran.dg/save_parameter.f90 b/gcc/testsuite/gfortran.dg/save_parameter.f90 index dd879bb869d0..9020ac5eac24 100644 --- a/gcc/testsuite/gfortran.dg/save_parameter.f90 +++ b/gcc/testsuite/gfortran.dg/save_parameter.f90 @@ -6,5 +6,3 @@ MODULE test CHARACTER(len=1), PARAMETER :: backslash = '\\' PUBLIC :: backslash END MODULE - -! { dg-final { cleanup-modules "test" } } diff --git a/gcc/testsuite/gfortran.dg/select_type_10.f03 b/gcc/testsuite/gfortran.dg/select_type_10.f03 index 217d72a8371e..0db9af9599e8 100644 --- a/gcc/testsuite/gfortran.dg/select_type_10.f03 +++ b/gcc/testsuite/gfortran.dg/select_type_10.f03 @@ -30,5 +30,3 @@ contains end function end module - -! { dg-final { cleanup-modules "bar_module" } } diff --git a/gcc/testsuite/gfortran.dg/select_type_15.f03 b/gcc/testsuite/gfortran.dg/select_type_15.f03 index 6be045c097e0..f408527d602f 100644 --- a/gcc/testsuite/gfortran.dg/select_type_15.f03 +++ b/gcc/testsuite/gfortran.dg/select_type_15.f03 @@ -72,6 +72,3 @@ program bug20 end select end program bug20 - - -! { dg-final { cleanup-modules "base_mat_mod d_base_mat_mod" } } diff --git a/gcc/testsuite/gfortran.dg/select_type_16.f03 b/gcc/testsuite/gfortran.dg/select_type_16.f03 index 29d19300a1b9..109252ee547b 100644 --- a/gcc/testsuite/gfortran.dg/select_type_16.f03 +++ b/gcc/testsuite/gfortran.dg/select_type_16.f03 @@ -36,6 +36,3 @@ contains end subroutine bug21 end module d_base_mat_mod - - -! { dg-final { cleanup-modules "d_base_mat_mod" } } diff --git a/gcc/testsuite/gfortran.dg/select_type_18.f03 b/gcc/testsuite/gfortran.dg/select_type_18.f03 index e4bacd377e75..e2a481d31692 100644 --- a/gcc/testsuite/gfortran.dg/select_type_18.f03 +++ b/gcc/testsuite/gfortran.dg/select_type_18.f03 @@ -86,5 +86,3 @@ subroutine trans2(a,b) return end subroutine trans2 - -! { dg-final { cleanup-modules "base_mod s_base_mod" } } diff --git a/gcc/testsuite/gfortran.dg/select_type_4.f90 b/gcc/testsuite/gfortran.dg/select_type_4.f90 index 95488e5f72cc..7e12d9354478 100644 --- a/gcc/testsuite/gfortran.dg/select_type_4.f90 +++ b/gcc/testsuite/gfortran.dg/select_type_4.f90 @@ -172,4 +172,3 @@ program main call destroy_list(list) stop end program main -! { dg-final { cleanup-modules "poly_list" } } diff --git a/gcc/testsuite/gfortran.dg/sequence_types_1.f90 b/gcc/testsuite/gfortran.dg/sequence_types_1.f90 index 62cd8fd68868..6c0bb247c875 100644 --- a/gcc/testsuite/gfortran.dg/sequence_types_1.f90 +++ b/gcc/testsuite/gfortran.dg/sequence_types_1.f90 @@ -77,4 +77,3 @@ module data_types Integer(kindInt), dimension(:), pointer :: subset end type GroupDefLL end module data_types -! { dg-final { cleanup-modules "data_types" } } diff --git a/gcc/testsuite/gfortran.dg/sibling_dummy_procedure_1.f90 b/gcc/testsuite/gfortran.dg/sibling_dummy_procedure_1.f90 index c632c5b1b157..2c7acbe1ba50 100644 --- a/gcc/testsuite/gfortran.dg/sibling_dummy_procedure_1.f90 +++ b/gcc/testsuite/gfortran.dg/sibling_dummy_procedure_1.f90 @@ -30,5 +30,3 @@ contains call bar(self, z) end subroutine end - -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/sibling_dummy_procedure_2.f90 b/gcc/testsuite/gfortran.dg/sibling_dummy_procedure_2.f90 index 3bd3164995b0..042666016f79 100644 --- a/gcc/testsuite/gfortran.dg/sibling_dummy_procedure_2.f90 +++ b/gcc/testsuite/gfortran.dg/sibling_dummy_procedure_2.f90 @@ -30,5 +30,3 @@ contains call bar_(self, z) end subroutine end - -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/sibling_dummy_procedure_3.f90 b/gcc/testsuite/gfortran.dg/sibling_dummy_procedure_3.f90 index 21bdceead95f..5f1391edb60e 100644 --- a/gcc/testsuite/gfortran.dg/sibling_dummy_procedure_3.f90 +++ b/gcc/testsuite/gfortran.dg/sibling_dummy_procedure_3.f90 @@ -16,5 +16,3 @@ module ice end subroutine bar end subroutine foo end module - -! { dg-final { cleanup-modules "ice" } } diff --git a/gcc/testsuite/gfortran.dg/simplify_argN_1.f90 b/gcc/testsuite/gfortran.dg/simplify_argN_1.f90 index 933b1f32af7a..6cc64715c6b2 100644 --- a/gcc/testsuite/gfortran.dg/simplify_argN_1.f90 +++ b/gcc/testsuite/gfortran.dg/simplify_argN_1.f90 @@ -23,4 +23,3 @@ END MODULE MODS if (any (ISHFTC(X, 3, 5) /= D)) call abort () if (any (ISHFTC(X, Y, 5) /= E)) call abort () end -! { dg-final { cleanup-modules "mods" } } diff --git a/gcc/testsuite/gfortran.dg/spec_expr_4.f90 b/gcc/testsuite/gfortran.dg/spec_expr_4.f90 index cf655b920bd6..7b2d5b6be13b 100644 --- a/gcc/testsuite/gfortran.dg/spec_expr_4.f90 +++ b/gcc/testsuite/gfortran.dg/spec_expr_4.f90 @@ -31,4 +31,3 @@ end module global_numbering e%numbering => ent print *, element_local_coords (e) end -! { dg-final { cleanup-modules "elements global_numbering" } } diff --git a/gcc/testsuite/gfortran.dg/spec_expr_6.f90 b/gcc/testsuite/gfortran.dg/spec_expr_6.f90 index 3b5b973ecd45..2d15b31a1e46 100644 --- a/gcc/testsuite/gfortran.dg/spec_expr_6.f90 +++ b/gcc/testsuite/gfortran.dg/spec_expr_6.f90 @@ -48,5 +48,3 @@ contains p1_type = 42 end function p1_type end module m2 - -! { dg-final { cleanup-modules "m m2" } } diff --git a/gcc/testsuite/gfortran.dg/specification_type_resolution_1.f90 b/gcc/testsuite/gfortran.dg/specification_type_resolution_1.f90 index b830b5dfc7d6..1e4bb08b320d 100644 --- a/gcc/testsuite/gfortran.dg/specification_type_resolution_1.f90 +++ b/gcc/testsuite/gfortran.dg/specification_type_resolution_1.f90 @@ -28,4 +28,3 @@ end module test print *, elements_uncommon_with (z) print *, n_elements_uncommon_with_ (z) end -! { dg-final { cleanup-modules "test" } } diff --git a/gcc/testsuite/gfortran.dg/specification_type_resolution_2.f90 b/gcc/testsuite/gfortran.dg/specification_type_resolution_2.f90 index 0fcb7bd873ce..f87cd11b0b12 100644 --- a/gcc/testsuite/gfortran.dg/specification_type_resolution_2.f90 +++ b/gcc/testsuite/gfortran.dg/specification_type_resolution_2.f90 @@ -21,5 +21,3 @@ contains end function bar end module gfcbug50 - -! { dg-final { cleanup-modules "gfcbug50" } } diff --git a/gcc/testsuite/gfortran.dg/stfunc_5.f90 b/gcc/testsuite/gfortran.dg/stfunc_5.f90 index 09b6da338f42..49170208af58 100644 --- a/gcc/testsuite/gfortran.dg/stfunc_5.f90 +++ b/gcc/testsuite/gfortran.dg/stfunc_5.f90 @@ -6,6 +6,3 @@ MODULE stmt f(x) = x**2 ! { dg-error "Unexpected STATEMENT FUNCTION" } END MODULE - -! { dg-final { cleanup-modules "stmt" } } - diff --git a/gcc/testsuite/gfortran.dg/string_compare_2.f90 b/gcc/testsuite/gfortran.dg/string_compare_2.f90 index 966ed554ab52..dc68bef2ada6 100644 --- a/gcc/testsuite/gfortran.dg/string_compare_2.f90 +++ b/gcc/testsuite/gfortran.dg/string_compare_2.f90 @@ -35,5 +35,3 @@ program pack_bug end if end do end - -! { dg-final { cleanup-modules "xparams" } } diff --git a/gcc/testsuite/gfortran.dg/structure_constructor_10.f90 b/gcc/testsuite/gfortran.dg/structure_constructor_10.f90 index eed7fa3a9d27..3231571244ad 100644 --- a/gcc/testsuite/gfortran.dg/structure_constructor_10.f90 +++ b/gcc/testsuite/gfortran.dg/structure_constructor_10.f90 @@ -23,6 +23,3 @@ SUBROUTINE cdf_beta() IMPLICIT NONE CALL check_complements(the_beta%name) END SUBROUTINE cdf_beta - -! { dg-final { cleanup-modules "cdf_aux_mod" } } - diff --git a/gcc/testsuite/gfortran.dg/structure_constructor_8.f03 b/gcc/testsuite/gfortran.dg/structure_constructor_8.f03 index b86d0ecccaf0..1c0ecd1c1a46 100644 --- a/gcc/testsuite/gfortran.dg/structure_constructor_8.f03 +++ b/gcc/testsuite/gfortran.dg/structure_constructor_8.f03 @@ -58,4 +58,3 @@ PROGRAM test WRITE (*,*) ispriv_t (5) ! { dg-error "has no IMPLICIT type" } END PROGRAM test -! { dg-final { cleanup-modules "privmod" } } diff --git a/gcc/testsuite/gfortran.dg/substr_1.f90 b/gcc/testsuite/gfortran.dg/substr_1.f90 index a811d9688cc5..98164304b0b1 100644 --- a/gcc/testsuite/gfortran.dg/substr_1.f90 +++ b/gcc/testsuite/gfortran.dg/substr_1.f90 @@ -10,5 +10,3 @@ use m character(4) :: b b = a end - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/substring_equivalence.f90 b/gcc/testsuite/gfortran.dg/substring_equivalence.f90 index 1d0c0cd84225..1a01024bc110 100644 --- a/gcc/testsuite/gfortran.dg/substring_equivalence.f90 +++ b/gcc/testsuite/gfortran.dg/substring_equivalence.f90 @@ -6,5 +6,3 @@ module FLAGS character :: at, dev equivalence ( encodings(1:1),at ), ( encodings(2:2),dev) end module FLAGS - -! { dg-final { cleanup-modules "flags" } } diff --git a/gcc/testsuite/gfortran.dg/test_com_block.f90 b/gcc/testsuite/gfortran.dg/test_com_block.f90 index 37175d265305..df3f643e72d5 100644 --- a/gcc/testsuite/gfortran.dg/test_com_block.f90 +++ b/gcc/testsuite/gfortran.dg/test_com_block.f90 @@ -30,5 +30,3 @@ program testComBlock call abort() endif end program testComBlock - -! { dg-final { cleanup-modules "nonf03comblock" } } diff --git a/gcc/testsuite/gfortran.dg/test_common_binding_labels.f03 b/gcc/testsuite/gfortran.dg/test_common_binding_labels.f03 index ea9a59a35e4c..554a59dfc9c6 100644 --- a/gcc/testsuite/gfortran.dg/test_common_binding_labels.f03 +++ b/gcc/testsuite/gfortran.dg/test_common_binding_labels.f03 @@ -38,5 +38,3 @@ module z integer(c_int) :: i bind(c, name="mycom2") /com2/ end module z - -! { dg-final { cleanup-modules "x y" } } diff --git a/gcc/testsuite/gfortran.dg/test_only_clause.f90 b/gcc/testsuite/gfortran.dg/test_only_clause.f90 index a02a75922bf4..7c63e2be1679 100644 --- a/gcc/testsuite/gfortran.dg/test_only_clause.f90 +++ b/gcc/testsuite/gfortran.dg/test_only_clause.f90 @@ -18,5 +18,3 @@ module testOnlyClause endif end subroutine testOnly end module testOnlyClause - -! { dg-final { cleanup-modules "testonlyclause" } } diff --git a/gcc/testsuite/gfortran.dg/transfer_assumed_size_1.f90 b/gcc/testsuite/gfortran.dg/transfer_assumed_size_1.f90 index 1b0e1567160e..c1485a65cf52 100644 --- a/gcc/testsuite/gfortran.dg/transfer_assumed_size_1.f90 +++ b/gcc/testsuite/gfortran.dg/transfer_assumed_size_1.f90 @@ -41,5 +41,3 @@ program main call BytesToString( StringToBytes('Hi'), str ) if (trim(str) .ne. "Hi") call abort () end program -! { dg-final { cleanup-modules "transferbug" } } - diff --git a/gcc/testsuite/gfortran.dg/transfer_intrinsic_3.f90 b/gcc/testsuite/gfortran.dg/transfer_intrinsic_3.f90 index f0b9b5468779..d993da25d8d2 100644 --- a/gcc/testsuite/gfortran.dg/transfer_intrinsic_3.f90 +++ b/gcc/testsuite/gfortran.dg/transfer_intrinsic_3.f90 @@ -35,4 +35,3 @@ end module m end do deallocate(qname) end -! { dg-final { cleanup-modules "m" } } \ No newline at end of file diff --git a/gcc/testsuite/gfortran.dg/transpose_optimization_1.f90 b/gcc/testsuite/gfortran.dg/transpose_optimization_1.f90 index d0ba6c495c10..885ff7c20349 100644 --- a/gcc/testsuite/gfortran.dg/transpose_optimization_1.f90 +++ b/gcc/testsuite/gfortran.dg/transpose_optimization_1.f90 @@ -104,4 +104,3 @@ end module foo ! { dg-final { scan-tree-dump-times "struct\[^\\n\]*atmp" 4 "original" } } ! { dg-final { cleanup-tree-dump "original" } } -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/transpose_optimization_2.f90 b/gcc/testsuite/gfortran.dg/transpose_optimization_2.f90 index ba03374078b1..54ef8417eb95 100644 --- a/gcc/testsuite/gfortran.dg/transpose_optimization_2.f90 +++ b/gcc/testsuite/gfortran.dg/transpose_optimization_2.f90 @@ -63,4 +63,3 @@ end ! { dg-final { scan-tree-dump-times "parm" 66 "original" } } ! { dg-final { scan-tree-dump-times "atmp" 12 "original" } } ! { dg-final { cleanup-tree-dump "original" } } -! { dg-final { cleanup-modules "mod" } } diff --git a/gcc/testsuite/gfortran.dg/trim_optimize_2.f90 b/gcc/testsuite/gfortran.dg/trim_optimize_2.f90 index 46ae7fb88c4f..b7ae1e3e5330 100644 --- a/gcc/testsuite/gfortran.dg/trim_optimize_2.f90 +++ b/gcc/testsuite/gfortran.dg/trim_optimize_2.f90 @@ -35,4 +35,3 @@ end program main ! { dg-final { scan-tree-dump-times "memmove" 4 "original" } } ! { dg-final { scan-tree-dump-times "string_trim" 0 "original" } } ! { dg-final { cleanup-tree-dump "original" } } -! { dg-final { cleanup-modules "faz" } } diff --git a/gcc/testsuite/gfortran.dg/trim_optimize_6.f90 b/gcc/testsuite/gfortran.dg/trim_optimize_6.f90 index 2be4a347bc97..2303bb4ef78b 100644 --- a/gcc/testsuite/gfortran.dg/trim_optimize_6.f90 +++ b/gcc/testsuite/gfortran.dg/trim_optimize_6.f90 @@ -23,5 +23,3 @@ program main if (line /= "aX ") call abort if (f() .ne. 2) call abort end program main - -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/type_decl_1.f90 b/gcc/testsuite/gfortran.dg/type_decl_1.f90 index 93928652a05d..badb9aeaefe6 100644 --- a/gcc/testsuite/gfortran.dg/type_decl_1.f90 +++ b/gcc/testsuite/gfortran.dg/type_decl_1.f90 @@ -26,5 +26,3 @@ type(integer (kind=k4)) function f() use m f = 42 end - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_assignment_1.f03 b/gcc/testsuite/gfortran.dg/typebound_assignment_1.f03 index 359572b0a51e..2d06097902d0 100644 --- a/gcc/testsuite/gfortran.dg/typebound_assignment_1.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_assignment_1.f03 @@ -31,5 +31,3 @@ contains this%st = st end subroutine init_comps end module hydro_flow - -! { dg-final { cleanup-modules "hydro_state hydro_flow" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_assignment_2.f03 b/gcc/testsuite/gfortran.dg/typebound_assignment_2.f03 index 862535a8652c..ca994dd4dbef 100644 --- a/gcc/testsuite/gfortran.dg/typebound_assignment_2.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_assignment_2.f03 @@ -35,5 +35,3 @@ contains this%gr = gr end subroutine init_comps end module hydro_flow - -! { dg-final { cleanup-modules "hydro_grid hydro_flow" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_assignment_3.f03 b/gcc/testsuite/gfortran.dg/typebound_assignment_3.f03 index 2001589a9ca3..9379570bda0c 100644 --- a/gcc/testsuite/gfortran.dg/typebound_assignment_3.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_assignment_3.f03 @@ -26,5 +26,3 @@ end module type (bar) :: foobar(2) foobar = bar() ! There was a not-implemented error here end - -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_call_1.f03 b/gcc/testsuite/gfortran.dg/typebound_call_1.f03 index d0da0ecd9948..4e7797bdf528 100644 --- a/gcc/testsuite/gfortran.dg/typebound_call_1.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_call_1.f03 @@ -94,5 +94,3 @@ PROGRAM main USE m, ONLY: test CALL test () END PROGRAM main - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_call_10.f03 b/gcc/testsuite/gfortran.dg/typebound_call_10.f03 index ca6038e45cef..22a2a72ba68f 100644 --- a/gcc/testsuite/gfortran.dg/typebound_call_10.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_call_10.f03 @@ -34,6 +34,3 @@ call t1%foo() call t2%foo() call t1%foo(t2) end - -! { dg-final { cleanup-modules "m" } } - diff --git a/gcc/testsuite/gfortran.dg/typebound_call_11.f03 b/gcc/testsuite/gfortran.dg/typebound_call_11.f03 index 8d7b8f06178f..fa3693e726e6 100644 --- a/gcc/testsuite/gfortran.dg/typebound_call_11.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_call_11.f03 @@ -44,5 +44,3 @@ contains end function new_field3 end module - -! { dg-final { cleanup-modules "grid_module field_module" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_call_12.f03 b/gcc/testsuite/gfortran.dg/typebound_call_12.f03 index 5591dd9f19a2..f36b82689e03 100644 --- a/gcc/testsuite/gfortran.dg/typebound_call_12.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_call_12.f03 @@ -33,4 +33,3 @@ PROGRAM ProgA END DO END PROGRAM ProgA -! { dg-final { cleanup-modules "moda" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_call_13.f03 b/gcc/testsuite/gfortran.dg/typebound_call_13.f03 index 0800ba50526e..db220787e55f 100644 --- a/gcc/testsuite/gfortran.dg/typebound_call_13.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_call_13.f03 @@ -39,5 +39,3 @@ program test_optional if (res /= 2) call abort() end program - -! { dg-final { cleanup-modules "module_myobj" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_call_14.f03 b/gcc/testsuite/gfortran.dg/typebound_call_14.f03 index e8cbf846e5d6..e39b38d6ee6a 100644 --- a/gcc/testsuite/gfortran.dg/typebound_call_14.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_call_14.f03 @@ -25,5 +25,3 @@ contains print *,ice_array(2)%next%ice_fun() end subroutine end module ice_module - -! { dg-final { cleanup-modules "ice_module" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_call_15.f03 b/gcc/testsuite/gfortran.dg/typebound_call_15.f03 index ac6a668cc462..843dff4affc4 100644 --- a/gcc/testsuite/gfortran.dg/typebound_call_15.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_call_15.f03 @@ -22,4 +22,3 @@ contains end subroutine end module ice5 -! { dg-final { cleanup-modules "ice5" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_call_16.f03 b/gcc/testsuite/gfortran.dg/typebound_call_16.f03 index fdd60c603cce..39831957aa81 100644 --- a/gcc/testsuite/gfortran.dg/typebound_call_16.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_call_16.f03 @@ -31,5 +31,3 @@ end module base_mat_mod m = a%get_nrows() end - -! { dg-final { cleanup-modules "base_mat_mod" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_call_17.f03 b/gcc/testsuite/gfortran.dg/typebound_call_17.f03 index 5bd054707ec6..599685762564 100644 --- a/gcc/testsuite/gfortran.dg/typebound_call_17.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_call_17.f03 @@ -53,5 +53,3 @@ program test_poly call p1%add_poly() end program test_poly - -! { dg-final { cleanup-modules "polynomial" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_call_18.f03 b/gcc/testsuite/gfortran.dg/typebound_call_18.f03 index bb94717ad3ff..e417ebf9189e 100644 --- a/gcc/testsuite/gfortran.dg/typebound_call_18.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_call_18.f03 @@ -63,5 +63,3 @@ program main call g%assign (g_initial) print *, "cg: after g%assign" end program main - -! { dg-final { cleanup-modules "abstract_vector concrete_vector concrete_gradient" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_call_19.f03 b/gcc/testsuite/gfortran.dg/typebound_call_19.f03 index 95b272a80ab8..3c8b7684c670 100644 --- a/gcc/testsuite/gfortran.dg/typebound_call_19.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_call_19.f03 @@ -47,5 +47,3 @@ program test this%x = this%find_x() if (this%x%i /= 4) call abort() end - -! { dg-final { cleanup-modules "class_t" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_call_2.f03 b/gcc/testsuite/gfortran.dg/typebound_call_2.f03 index 5d70f7c17ef8..d0846f4149a8 100644 --- a/gcc/testsuite/gfortran.dg/typebound_call_2.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_call_2.f03 @@ -86,5 +86,3 @@ PROGRAM main USE m, ONLY: test CALL test () END PROGRAM main - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_call_20.f03 b/gcc/testsuite/gfortran.dg/typebound_call_20.f03 index 61eee5ba004d..8ee7302c5464 100644 --- a/gcc/testsuite/gfortran.dg/typebound_call_20.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_call_20.f03 @@ -37,5 +37,3 @@ program p y = this%find_y() if (y/=3) call abort() end - -! { dg-final { cleanup-modules "class_t" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_call_21.f03 b/gcc/testsuite/gfortran.dg/typebound_call_21.f03 index 5f7d67283c42..e31bd6de41db 100644 --- a/gcc/testsuite/gfortran.dg/typebound_call_21.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_call_21.f03 @@ -34,6 +34,4 @@ end module m end ! { dg-final { scan-tree-dump-times "_vptr->" 0 "original" } } - -! { dg-final { cleanup-modules "m" } } ! { dg-final { cleanup-tree-dump "original" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_call_22.f03 b/gcc/testsuite/gfortran.dg/typebound_call_22.f03 index b5aa8eef7899..31e5894372cf 100644 --- a/gcc/testsuite/gfortran.dg/typebound_call_22.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_call_22.f03 @@ -28,5 +28,3 @@ end program ! { dg-final { scan-tree-dump-times "base \\(\\);" 1 "optimized" } } ! { dg-final { cleanup-tree-dump "optimized" } } - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_call_3.f03 b/gcc/testsuite/gfortran.dg/typebound_call_3.f03 index eabb28ef18bc..ba7188624f18 100644 --- a/gcc/testsuite/gfortran.dg/typebound_call_3.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_call_3.f03 @@ -44,5 +44,3 @@ PROGRAM main CALL abort () END IF END PROGRAM main - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_call_4.f03 b/gcc/testsuite/gfortran.dg/typebound_call_4.f03 index 6cb5e69e3e94..c56f22d8804b 100644 --- a/gcc/testsuite/gfortran.dg/typebound_call_4.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_call_4.f03 @@ -47,5 +47,3 @@ CONTAINS END SUBROUTINE test END MODULE m - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_call_5.f03 b/gcc/testsuite/gfortran.dg/typebound_call_5.f03 index d9a845b073bc..3691292b5424 100644 --- a/gcc/testsuite/gfortran.dg/typebound_call_5.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_call_5.f03 @@ -37,5 +37,3 @@ SUBROUTINE test2 () CALL obj%priv () ! { dg-error "PRIVATE" } CALL obj%publ () END SUBROUTINE test2 - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_call_6.f03 b/gcc/testsuite/gfortran.dg/typebound_call_6.f03 index 0ad510edaed1..fbecabd061d8 100644 --- a/gcc/testsuite/gfortran.dg/typebound_call_6.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_call_6.f03 @@ -41,5 +41,3 @@ PROGRAM main CALL super%proc CALL sub%proc END PROGRAM main - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_call_7.f03 b/gcc/testsuite/gfortran.dg/typebound_call_7.f03 index 03a1a51ccd4c..7e7209c198a9 100644 --- a/gcc/testsuite/gfortran.dg/typebound_call_7.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_call_7.f03 @@ -46,5 +46,3 @@ CONTAINS END SUBROUTINE fill_gap END MODULE touching - -! { dg-final { cleanup-modules "touching" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_call_8.f03 b/gcc/testsuite/gfortran.dg/typebound_call_8.f03 index 3f65846b3e58..1784ccefa7b3 100644 --- a/gcc/testsuite/gfortran.dg/typebound_call_8.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_call_8.f03 @@ -28,5 +28,3 @@ CONTAINS END SUBROUTINE fill_gap END MODULE touching - -! { dg-final { cleanup-modules "touching" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_call_9.f03 b/gcc/testsuite/gfortran.dg/typebound_call_9.f03 index 4863f07eb596..c40850610e16 100644 --- a/gcc/testsuite/gfortran.dg/typebound_call_9.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_call_9.f03 @@ -56,5 +56,3 @@ contains End Subroutine foo_free end module foo_mod - -! { dg-final { cleanup-modules "foo_mod" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_generic_1.f03 b/gcc/testsuite/gfortran.dg/typebound_generic_1.f03 index fb1dfaec663d..f9c471ae96af 100644 --- a/gcc/testsuite/gfortran.dg/typebound_generic_1.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_generic_1.f03 @@ -92,5 +92,3 @@ CONTAINS END SUBROUTINE subr END MODULE m - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_generic_10.f03 b/gcc/testsuite/gfortran.dg/typebound_generic_10.f03 index 590fa5278abf..56952e1b9015 100644 --- a/gcc/testsuite/gfortran.dg/typebound_generic_10.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_generic_10.f03 @@ -28,5 +28,3 @@ contains end subroutine b_subroutine end module generic - -! { dg-final { cleanup-modules "generic" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_generic_11.f90 b/gcc/testsuite/gfortran.dg/typebound_generic_11.f90 index eb89d0dfe200..c71f6863305f 100644 --- a/gcc/testsuite/gfortran.dg/typebound_generic_11.f90 +++ b/gcc/testsuite/gfortran.dg/typebound_generic_11.f90 @@ -59,5 +59,3 @@ contains res = ( t%i == i ) end function i_equal_t2 end module m_test2 - -! { dg-final { cleanup-modules "m_test m_test2" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_generic_2.f03 b/gcc/testsuite/gfortran.dg/typebound_generic_2.f03 index c18b306b906a..8094d863ffae 100644 --- a/gcc/testsuite/gfortran.dg/typebound_generic_2.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_generic_2.f03 @@ -60,5 +60,3 @@ PROGRAM main WRITE (*,*) myobj%sub (1) ! { dg-error "FUNCTION" } END PROGRAM main - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_generic_3.f03 b/gcc/testsuite/gfortran.dg/typebound_generic_3.f03 index d56f914897e3..6f7af2eafb6d 100644 --- a/gcc/testsuite/gfortran.dg/typebound_generic_3.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_generic_3.f03 @@ -59,4 +59,3 @@ PROGRAM main END PROGRAM main ! { dg-output "Plain Integer(\n|\r\n|\r).*Plain Real(\n|\r\n|\r).*Passed Integer(\n|\r\n|\r).*Passed Real" } -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_generic_4.f03 b/gcc/testsuite/gfortran.dg/typebound_generic_4.f03 index ff5cd0582cdf..a74cdae75089 100644 --- a/gcc/testsuite/gfortran.dg/typebound_generic_4.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_generic_4.f03 @@ -51,4 +51,3 @@ program foobar end program foobar ! { dg-output "Vector.*Matrix" } -! { dg-final { cleanup-modules "bar_mod" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_generic_5.f03 b/gcc/testsuite/gfortran.dg/typebound_generic_5.f03 index 3fd94b154fb2..561fcce1c3c0 100644 --- a/gcc/testsuite/gfortran.dg/typebound_generic_5.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_generic_5.f03 @@ -51,5 +51,3 @@ PROGRAM main CALL abort () END IF END PROGRAM main - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_generic_6.f03 b/gcc/testsuite/gfortran.dg/typebound_generic_6.f03 index 973e10a35e39..d0a17567ab43 100644 --- a/gcc/testsuite/gfortran.dg/typebound_generic_6.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_generic_6.f03 @@ -65,5 +65,3 @@ program testd15 if (afab%get() .ne. 3) call abort end program testd15 - -! { dg-final { cleanup-modules "foo_mod foo2_mod" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_generic_7.f03 b/gcc/testsuite/gfortran.dg/typebound_generic_7.f03 index 2519ab09416b..cb551b81bdb8 100644 --- a/gcc/testsuite/gfortran.dg/typebound_generic_7.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_generic_7.f03 @@ -24,5 +24,3 @@ contains call x%do() end subroutine end - -! { dg-final { cleanup-modules "foo_mod" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_generic_8.f03 b/gcc/testsuite/gfortran.dg/typebound_generic_8.f03 index 0ee6610e1733..2c507e14c337 100644 --- a/gcc/testsuite/gfortran.dg/typebound_generic_8.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_generic_8.f03 @@ -25,5 +25,3 @@ contains end subroutine do_something end module ice6 - -! { dg-final { cleanup-modules "ice6" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_generic_9.f03 b/gcc/testsuite/gfortran.dg/typebound_generic_9.f03 index f85bb3857062..42be60219e59 100644 --- a/gcc/testsuite/gfortran.dg/typebound_generic_9.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_generic_9.f03 @@ -58,6 +58,4 @@ program testd15 if (af2%get() .ne. 3) call abort end program testd15 - -! { dg-final { cleanup-modules "foo_mod foo2_mod" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_operator_1.f03 b/gcc/testsuite/gfortran.dg/typebound_operator_1.f03 index f756a595b402..962c2bda8cdc 100644 --- a/gcc/testsuite/gfortran.dg/typebound_operator_1.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_operator_1.f03 @@ -45,5 +45,3 @@ CONTAINS END SUBROUTINE assign_proc END MODULE m - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_operator_10.f03 b/gcc/testsuite/gfortran.dg/typebound_operator_10.f03 index 146eab01576e..e8f9f1e2dbf6 100644 --- a/gcc/testsuite/gfortran.dg/typebound_operator_10.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_operator_10.f03 @@ -26,4 +26,3 @@ program main class(field) ,pointer :: u u = (u)*2. ! { dg-error "check that there is a matching specific" } end program -! { dg-final { cleanup-modules "field_module" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_operator_11.f90 b/gcc/testsuite/gfortran.dg/typebound_operator_11.f90 index 1f5c19530d84..b37e97521130 100644 --- a/gcc/testsuite/gfortran.dg/typebound_operator_11.f90 +++ b/gcc/testsuite/gfortran.dg/typebound_operator_11.f90 @@ -38,5 +38,3 @@ contains x = x%t()*dt end subroutine end module - -! { dg-final { cleanup-modules "foo_module" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_operator_12.f03 b/gcc/testsuite/gfortran.dg/typebound_operator_12.f03 index 3496ed38639d..4f729570b00f 100644 --- a/gcc/testsuite/gfortran.dg/typebound_operator_12.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_operator_12.f03 @@ -41,5 +41,3 @@ program main if (any (fireworks%position .ne. [6, 12, 18])) call abort if (any (fireworks%velocity .ne. [24, 30, 36])) call abort end program -! { dg-final { cleanup-modules "soop_stars_class" } } - diff --git a/gcc/testsuite/gfortran.dg/typebound_operator_13.f03 b/gcc/testsuite/gfortran.dg/typebound_operator_13.f03 index e1371c8a8178..498289429352 100644 --- a/gcc/testsuite/gfortran.dg/typebound_operator_13.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_operator_13.f03 @@ -55,5 +55,3 @@ program main if (any (fireworks%position .ne. [6, 12, 18])) call abort if (any (fireworks%velocity .ne. [24, 30, 36])) call abort end program -! { dg-final { cleanup-modules "soop_stars_class" } } - diff --git a/gcc/testsuite/gfortran.dg/typebound_operator_2.f03 b/gcc/testsuite/gfortran.dg/typebound_operator_2.f03 index cae2cdab71fe..67b6b5e0326f 100644 --- a/gcc/testsuite/gfortran.dg/typebound_operator_2.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_operator_2.f03 @@ -63,5 +63,3 @@ CONTAINS END SUBROUTINE sub2 END MODULE m - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_operator_3.f03 b/gcc/testsuite/gfortran.dg/typebound_operator_3.f03 index 51ad1d2f0f83..c558dfda36b1 100644 --- a/gcc/testsuite/gfortran.dg/typebound_operator_3.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_operator_3.f03 @@ -121,5 +121,3 @@ PROGRAM main IF (.GET. num1 /= 3.0) CALL abort () END PROGRAM main - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_operator_4.f03 b/gcc/testsuite/gfortran.dg/typebound_operator_4.f03 index 835ceb63ff06..6ede14e878e2 100644 --- a/gcc/testsuite/gfortran.dg/typebound_operator_4.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_operator_4.f03 @@ -88,5 +88,3 @@ PROGRAM main x = x + 42 ! { dg-error "Operands of" } x = x .PLUS. 5 ! { dg-error "Unknown operator" } END PROGRAM main - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_operator_5.f03 b/gcc/testsuite/gfortran.dg/typebound_operator_5.f03 index 25a8c382d2ac..a6c9c2b5e4d1 100644 --- a/gcc/testsuite/gfortran.dg/typebound_operator_5.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_operator_5.f03 @@ -26,5 +26,3 @@ PROGRAM P CLASS (NODE),POINTER :: A, B PRINT *, A%PT .LT. B%PT END - -! { dg-final { cleanup-modules "def1" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_operator_6.f03 b/gcc/testsuite/gfortran.dg/typebound_operator_6.f03 index 132b32b6140b..02bd01a948a9 100644 --- a/gcc/testsuite/gfortran.dg/typebound_operator_6.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_operator_6.f03 @@ -69,5 +69,3 @@ PROGRAM TEST if (.NOT. NDA .LT. NDB) call abort() END - -! { dg-final { cleanup-modules "dat_mod node_mod" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_operator_7.f03 b/gcc/testsuite/gfortran.dg/typebound_operator_7.f03 index a7b0f81722af..280072d0ffa8 100644 --- a/gcc/testsuite/gfortran.dg/typebound_operator_7.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_operator_7.f03 @@ -99,5 +99,3 @@ program main type is (i_field); if (u%i .ne. 152064) call abort end select end program -! { dg-final { cleanup-modules "field_module i_field_module" } } - diff --git a/gcc/testsuite/gfortran.dg/typebound_operator_8.f03 b/gcc/testsuite/gfortran.dg/typebound_operator_8.f03 index a3726ba9f1ad..88d485d6a639 100644 --- a/gcc/testsuite/gfortran.dg/typebound_operator_8.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_operator_8.f03 @@ -97,4 +97,3 @@ program main if (u%i .ne. 152064) call abort end program -! { dg-final { cleanup-modules "field_module i_field_module" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_operator_9.f03 b/gcc/testsuite/gfortran.dg/typebound_operator_9.f03 index 9fda1eb580aa..6e625262c315 100644 --- a/gcc/testsuite/gfortran.dg/typebound_operator_9.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_operator_9.f03 @@ -498,4 +498,3 @@ contains end select end subroutine end program test_pde_solver -! { dg-final { cleanup-modules "pde_specific define_pde_objects cartesian_2d_objects base_pde_objects" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_override_1.f90 b/gcc/testsuite/gfortran.dg/typebound_override_1.f90 index c2b71933ac0b..a7e340e1b0be 100644 --- a/gcc/testsuite/gfortran.dg/typebound_override_1.f90 +++ b/gcc/testsuite/gfortran.dg/typebound_override_1.f90 @@ -121,5 +121,3 @@ contains end function end module w2 - -! { dg-final { cleanup-modules "m w1 w2" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_override_2.f90 b/gcc/testsuite/gfortran.dg/typebound_override_2.f90 index 98146b68141c..375875e734ab 100644 --- a/gcc/testsuite/gfortran.dg/typebound_override_2.f90 +++ b/gcc/testsuite/gfortran.dg/typebound_override_2.f90 @@ -28,5 +28,3 @@ contains integer, intent(inout) :: j end subroutine ext_bar end module extfoo_mod - -! { dg-final { cleanup-modules "foo_mod extfoo_mod" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_proc_1.f08 b/gcc/testsuite/gfortran.dg/typebound_proc_1.f08 index 53868a4632ce..674d4e028f65 100644 --- a/gcc/testsuite/gfortran.dg/typebound_proc_1.f08 +++ b/gcc/testsuite/gfortran.dg/typebound_proc_1.f08 @@ -65,5 +65,3 @@ CONTAINS END FUNCTION proc3 END MODULE testmod - -! { dg-final { cleanup-modules "testmod" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_proc_10.f03 b/gcc/testsuite/gfortran.dg/typebound_proc_10.f03 index 3f372c815f23..cbb61b6caa3c 100644 --- a/gcc/testsuite/gfortran.dg/typebound_proc_10.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_proc_10.f03 @@ -39,5 +39,3 @@ MODULE m2 END TYPE sub_type2 END MODULE m2 - -! { dg-final { cleanup-modules "m1" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_proc_11.f03 b/gcc/testsuite/gfortran.dg/typebound_proc_11.f03 index fafc149f574c..6105b8ca2f7c 100644 --- a/gcc/testsuite/gfortran.dg/typebound_proc_11.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_proc_11.f03 @@ -29,5 +29,3 @@ CONTAINS END SUBROUTINE realproc END MODULE testmod - -! { dg-final { cleanup-modules "testmod" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_proc_13.f03 b/gcc/testsuite/gfortran.dg/typebound_proc_13.f03 index 62054b6fa3fa..af486ff7684d 100644 --- a/gcc/testsuite/gfortran.dg/typebound_proc_13.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_proc_13.f03 @@ -45,5 +45,3 @@ CONTAINS END SUBROUTINE test END MODULE m - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_proc_14.f03 b/gcc/testsuite/gfortran.dg/typebound_proc_14.f03 index 766a0ef66c1b..1f0d7de3b350 100644 --- a/gcc/testsuite/gfortran.dg/typebound_proc_14.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_proc_14.f03 @@ -29,5 +29,3 @@ contains end subroutine end - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_proc_15.f03 b/gcc/testsuite/gfortran.dg/typebound_proc_15.f03 index 37907b3f4df3..31d10ca27163 100644 --- a/gcc/testsuite/gfortran.dg/typebound_proc_15.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_proc_15.f03 @@ -30,5 +30,3 @@ contains end subroutine end - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_proc_16.f03 b/gcc/testsuite/gfortran.dg/typebound_proc_16.f03 index 828f51022040..e43b3f8065f7 100644 --- a/gcc/testsuite/gfortran.dg/typebound_proc_16.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_proc_16.f03 @@ -54,5 +54,3 @@ MODULE rational_numbers r%d = a%d*b%d END FUNCTION END - -! { dg-final { cleanup-modules "rational_numbers" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_proc_17.f03 b/gcc/testsuite/gfortran.dg/typebound_proc_17.f03 index 5c1a1c30c573..4bc177b17a00 100644 --- a/gcc/testsuite/gfortran.dg/typebound_proc_17.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_proc_17.f03 @@ -21,6 +21,3 @@ function get_coeff(self) result(coeff) end function get_coeff end module array - - -! { dg-final { cleanup-modules "array" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_proc_18.f03 b/gcc/testsuite/gfortran.dg/typebound_proc_18.f03 index 956c02e267d1..725cba6d64db 100644 --- a/gcc/testsuite/gfortran.dg/typebound_proc_18.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_proc_18.f03 @@ -25,5 +25,3 @@ contains end function Tree_Node_Get end module Merger_Trees - -! { dg-final { cleanup-modules "merger_trees" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_proc_19.f90 b/gcc/testsuite/gfortran.dg/typebound_proc_19.f90 index be15bf09fc34..b9068b65dd6d 100644 --- a/gcc/testsuite/gfortran.dg/typebound_proc_19.f90 +++ b/gcc/testsuite/gfortran.dg/typebound_proc_19.f90 @@ -39,5 +39,3 @@ end subroutine test call test() end - -! { dg-final { cleanup-modules "mytypes" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_proc_2.f90 b/gcc/testsuite/gfortran.dg/typebound_proc_2.f90 index 70ae2ca73231..a34d935eb064 100644 --- a/gcc/testsuite/gfortran.dg/typebound_proc_2.f90 +++ b/gcc/testsuite/gfortran.dg/typebound_proc_2.f90 @@ -29,6 +29,4 @@ CONTAINS END FUNCTION proc2 END MODULE testmod - -! { dg-final { cleanup-modules "testmod" } } ! { dg-excess-errors "no IMPLICIT type" } diff --git a/gcc/testsuite/gfortran.dg/typebound_proc_20.f90 b/gcc/testsuite/gfortran.dg/typebound_proc_20.f90 index 4fee2f3bab2f..b63daf97f959 100644 --- a/gcc/testsuite/gfortran.dg/typebound_proc_20.f90 +++ b/gcc/testsuite/gfortran.dg/typebound_proc_20.f90 @@ -64,5 +64,3 @@ use class_t type(t) :: x call x%calc() end - -! { dg-final { cleanup-modules "class_t" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_proc_21.f90 b/gcc/testsuite/gfortran.dg/typebound_proc_21.f90 index 6c16d46ff2ce..382f6d8a8fe6 100644 --- a/gcc/testsuite/gfortran.dg/typebound_proc_21.f90 +++ b/gcc/testsuite/gfortran.dg/typebound_proc_21.f90 @@ -23,5 +23,3 @@ contains find_x => null() end function find_x end module class_t - -! { dg-final { cleanup-modules "class_t" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_proc_22.f90 b/gcc/testsuite/gfortran.dg/typebound_proc_22.f90 index f7691c5f283d..2d9f17c564f6 100644 --- a/gcc/testsuite/gfortran.dg/typebound_proc_22.f90 +++ b/gcc/testsuite/gfortran.dg/typebound_proc_22.f90 @@ -45,5 +45,3 @@ bar = foo%getx() ! OK bar = fooPriv%getxPriv() ! { dg-error " is PRIVATE " } end program quicktest - -! { dg-final { cleanup-modules "qtest qtestpriv" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_proc_23.f90 b/gcc/testsuite/gfortran.dg/typebound_proc_23.f90 index ff682a41b367..0109c7478de4 100644 --- a/gcc/testsuite/gfortran.dg/typebound_proc_23.f90 +++ b/gcc/testsuite/gfortran.dg/typebound_proc_23.f90 @@ -28,5 +28,3 @@ if (it/=0) call abort() call ice_sub(t) if (it/=1) call abort() end - -! { dg-final { cleanup-modules "ice" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_proc_24.f03 b/gcc/testsuite/gfortran.dg/typebound_proc_24.f03 index f200e0efbbc3..e8ed9186f402 100644 --- a/gcc/testsuite/gfortran.dg/typebound_proc_24.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_proc_24.f03 @@ -28,5 +28,3 @@ contains end subroutine end module - -! { dg-final { cleanup-modules "datetime_mod" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_proc_25.f90 b/gcc/testsuite/gfortran.dg/typebound_proc_25.f90 index 4a68fb9db518..3646b65d9114 100644 --- a/gcc/testsuite/gfortran.dg/typebound_proc_25.f90 +++ b/gcc/testsuite/gfortran.dg/typebound_proc_25.f90 @@ -106,5 +106,3 @@ end module CALL factory%finalize() ! Destroy the object END PROGRAM main - -! { dg-final { cleanup-modules "factory_pattern" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_proc_3.f03 b/gcc/testsuite/gfortran.dg/typebound_proc_3.f03 index 13b90c14f29c..56cb9cfa8263 100644 --- a/gcc/testsuite/gfortran.dg/typebound_proc_3.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_proc_3.f03 @@ -13,5 +13,3 @@ MODULE testmod END TYPE t ! { dg-error "Fortran 2008" } END MODULE testmod - -! { dg-final { cleanup-modules "testmod" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_proc_4.f03 b/gcc/testsuite/gfortran.dg/typebound_proc_4.f03 index 60aa728a40ff..9b7a4fa5ddfe 100644 --- a/gcc/testsuite/gfortran.dg/typebound_proc_4.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_proc_4.f03 @@ -35,5 +35,3 @@ MODULE testmod CONTAINS END MODULE testmod - -! { dg-final { cleanup-modules "testmod" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_proc_5.f03 b/gcc/testsuite/gfortran.dg/typebound_proc_5.f03 index fdd15b388d1f..c80deed4ae3e 100644 --- a/gcc/testsuite/gfortran.dg/typebound_proc_5.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_proc_5.f03 @@ -115,5 +115,3 @@ CONTAINS END SUBROUTINE proc_no_module END PROGRAM main - -! { dg-final { cleanup-modules "othermod testmod" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_proc_6.f03 b/gcc/testsuite/gfortran.dg/typebound_proc_6.f03 index 36dc9b1ca86e..0f4f3118bf4b 100644 --- a/gcc/testsuite/gfortran.dg/typebound_proc_6.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_proc_6.f03 @@ -176,5 +176,3 @@ CONTAINS END SUBROUTINE proc_tmereal END MODULE testmod - -! { dg-final { cleanup-modules "testmod" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_proc_7.f03 b/gcc/testsuite/gfortran.dg/typebound_proc_7.f03 index ebf611e67e22..ecde98f5ddcb 100644 --- a/gcc/testsuite/gfortran.dg/typebound_proc_7.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_proc_7.f03 @@ -28,5 +28,3 @@ CONTAINS END SUBROUTINE proc_noarg END MODULE testmod - -! { dg-final { cleanup-modules "testmod" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_proc_8.f03 b/gcc/testsuite/gfortran.dg/typebound_proc_8.f03 index df7764d34744..ed5e422b6cf8 100644 --- a/gcc/testsuite/gfortran.dg/typebound_proc_8.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_proc_8.f03 @@ -33,5 +33,3 @@ CONTAINS END SUBROUTINE proc END MODULE testmod - -! { dg-final { cleanup-modules "testmod" } } diff --git a/gcc/testsuite/gfortran.dg/typebound_proc_9.f03 b/gcc/testsuite/gfortran.dg/typebound_proc_9.f03 index 9106de695799..3a96c0a92d4d 100644 --- a/gcc/testsuite/gfortran.dg/typebound_proc_9.f03 +++ b/gcc/testsuite/gfortran.dg/typebound_proc_9.f03 @@ -29,5 +29,3 @@ MODULE testmod END TYPE abstract_type END MODULE testmod - -! { dg-final { cleanup-modules "testmod" } } diff --git a/gcc/testsuite/gfortran.dg/unreferenced_use_assoc_1.f90 b/gcc/testsuite/gfortran.dg/unreferenced_use_assoc_1.f90 index b2fdd79cb66e..1f36b2d12d9f 100644 --- a/gcc/testsuite/gfortran.dg/unreferenced_use_assoc_1.f90 +++ b/gcc/testsuite/gfortran.dg/unreferenced_use_assoc_1.f90 @@ -37,4 +37,3 @@ program main call DoSomethingWithBytes( UserTypeToBytes(user) ) end program -! { dg-final { cleanup-modules "internalcompilererror" } } diff --git a/gcc/testsuite/gfortran.dg/unused_artificial_dummies_1.f90 b/gcc/testsuite/gfortran.dg/unused_artificial_dummies_1.f90 index bfeceaf5749d..68ceee7af331 100644 --- a/gcc/testsuite/gfortran.dg/unused_artificial_dummies_1.f90 +++ b/gcc/testsuite/gfortran.dg/unused_artificial_dummies_1.f90 @@ -47,4 +47,3 @@ contains end function end module foo -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/use_1.f90 b/gcc/testsuite/gfortran.dg/use_1.f90 index 2750d10d9b59..46d8fa9ea294 100644 --- a/gcc/testsuite/gfortran.dg/use_1.f90 +++ b/gcc/testsuite/gfortran.dg/use_1.f90 @@ -6,4 +6,3 @@ subroutine bar1 usefoo end - ! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/use_10.f90 b/gcc/testsuite/gfortran.dg/use_10.f90 index 3c752ed03881..e52fcff7e595 100644 --- a/gcc/testsuite/gfortran.dg/use_10.f90 +++ b/gcc/testsuite/gfortran.dg/use_10.f90 @@ -27,5 +27,3 @@ operator(.my.)=>operator(.op.),operator(.ops.)=>operator(.op.) implicit none if (.my.2 /= -2 .or. .op.3 /= -3 .or. .ops.7 /= -7) call abort() end - -! { dg-final { cleanup-modules "a" } } diff --git a/gcc/testsuite/gfortran.dg/use_11.f90 b/gcc/testsuite/gfortran.dg/use_11.f90 index ba7cf099503a..13530998480d 100644 --- a/gcc/testsuite/gfortran.dg/use_11.f90 +++ b/gcc/testsuite/gfortran.dg/use_11.f90 @@ -15,4 +15,3 @@ local1 = 5 local2 = 3 if (local1 .ne. local2) call abort () end -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/use_12.f90 b/gcc/testsuite/gfortran.dg/use_12.f90 index 7406dc433886..9a0c78c12c5e 100644 --- a/gcc/testsuite/gfortran.dg/use_12.f90 +++ b/gcc/testsuite/gfortran.dg/use_12.f90 @@ -23,4 +23,3 @@ program kmeans_driver integer :: nfirst(3) nfirst(1:numclusters) = get_nfirst( ) end program kmeans_driver -! { dg-final { cleanup-modules "m1 m2" } } diff --git a/gcc/testsuite/gfortran.dg/use_13.f90 b/gcc/testsuite/gfortran.dg/use_13.f90 index 1fe7b1eacf2d..2f6d4e7efcd9 100644 --- a/gcc/testsuite/gfortran.dg/use_13.f90 +++ b/gcc/testsuite/gfortran.dg/use_13.f90 @@ -42,4 +42,3 @@ end module m2 use m2 call test() end -! { dg-final { cleanup-modules "m m2" } } diff --git a/gcc/testsuite/gfortran.dg/use_14.f90 b/gcc/testsuite/gfortran.dg/use_14.f90 index 4ea5aed760c0..63f3dff98b05 100644 --- a/gcc/testsuite/gfortran.dg/use_14.f90 +++ b/gcc/testsuite/gfortran.dg/use_14.f90 @@ -17,5 +17,3 @@ subroutine my_sub (a) end subroutine END - -! { dg-final { cleanup-modules "test_mod" } } diff --git a/gcc/testsuite/gfortran.dg/use_15.f90 b/gcc/testsuite/gfortran.dg/use_15.f90 index 099588836e0f..bd5920aa0336 100644 --- a/gcc/testsuite/gfortran.dg/use_15.f90 +++ b/gcc/testsuite/gfortran.dg/use_15.f90 @@ -35,5 +35,3 @@ subroutine my_sub3 (a) end subroutine END - -! { dg-final { cleanup-modules "test_mod test_mod2" } } diff --git a/gcc/testsuite/gfortran.dg/use_16.f90 b/gcc/testsuite/gfortran.dg/use_16.f90 index 35176deedabc..7b22c415033d 100644 --- a/gcc/testsuite/gfortran.dg/use_16.f90 +++ b/gcc/testsuite/gfortran.dg/use_16.f90 @@ -14,5 +14,3 @@ use a ! { dg-error "Symbol 'bar' at \\(1\\) conflicts with symbol from module 'a implicit none integer :: bar ! { dg-error "Symbol 'bar' at \\(1\\) conflicts with symbol from module 'a'" } end - -! { dg-final { cleanup-modules "a" } } diff --git a/gcc/testsuite/gfortran.dg/use_17.f90 b/gcc/testsuite/gfortran.dg/use_17.f90 index b1b002e63161..d513920332c1 100644 --- a/gcc/testsuite/gfortran.dg/use_17.f90 +++ b/gcc/testsuite/gfortran.dg/use_17.f90 @@ -35,5 +35,3 @@ subroutine test1 integer :: c_double integer, parameter :: p1 = c_int, p2 = c_double_orig end subroutine test1 - -! { dg-final { cleanup-modules "mod1 mod2" } } diff --git a/gcc/testsuite/gfortran.dg/use_18.f90 b/gcc/testsuite/gfortran.dg/use_18.f90 index a46cdc407444..7975acd23e6e 100644 --- a/gcc/testsuite/gfortran.dg/use_18.f90 +++ b/gcc/testsuite/gfortran.dg/use_18.f90 @@ -47,5 +47,3 @@ type(t2) :: k = t2(1), l = t2(2) print *, i*j print *, k > l end - -! { dg-final { cleanup-modules "foo bar" } } diff --git a/gcc/testsuite/gfortran.dg/use_19.f90 b/gcc/testsuite/gfortran.dg/use_19.f90 index 5ddc5d153b2c..83ef713ce5fc 100644 --- a/gcc/testsuite/gfortran.dg/use_19.f90 +++ b/gcc/testsuite/gfortran.dg/use_19.f90 @@ -7,5 +7,3 @@ end module m use m, only: operator(/) ! { dg-error "Intrinsic operator '/' referenced at .1. not found in module 'm'" } end - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/use_20.f90 b/gcc/testsuite/gfortran.dg/use_20.f90 index 61a15d9e40d3..86e750987bd1 100644 --- a/gcc/testsuite/gfortran.dg/use_20.f90 +++ b/gcc/testsuite/gfortran.dg/use_20.f90 @@ -45,5 +45,3 @@ module merry_ICE use foo, only: foo_t ! <------ change order to prevent ICE use bar, only: bar_t ! <------ change order to prevent ICE end module merry_ICE - -! { dg-final { cleanup-modules "foo bar merry_ice" } } diff --git a/gcc/testsuite/gfortran.dg/use_21.f90 b/gcc/testsuite/gfortran.dg/use_21.f90 index eba412d9d781..4ec17513ec04 100644 --- a/gcc/testsuite/gfortran.dg/use_21.f90 +++ b/gcc/testsuite/gfortran.dg/use_21.f90 @@ -31,5 +31,3 @@ program ala implicit none call dom%init end program ala - -! { dg-final { cleanup-modules "domain" } } diff --git a/gcc/testsuite/gfortran.dg/use_3.f90 b/gcc/testsuite/gfortran.dg/use_3.f90 index 54100d191dda..1cfc71b2c2ed 100644 --- a/gcc/testsuite/gfortran.dg/use_3.f90 +++ b/gcc/testsuite/gfortran.dg/use_3.f90 @@ -9,4 +9,3 @@ end module foo use, nonintrinsic :: iso_fortran_env ! { dg-error "shall be either INTRINSIC or NON_INTRINSIC" } use, intrinsic :: iso_fortran_env end -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/use_4.f90 b/gcc/testsuite/gfortran.dg/use_4.f90 index b7249b0f0d69..a05689d3772d 100644 --- a/gcc/testsuite/gfortran.dg/use_4.f90 +++ b/gcc/testsuite/gfortran.dg/use_4.f90 @@ -31,4 +31,3 @@ program test_foo use foo, only: i => foo! { dg-error "been used as an external module name" } use foo, only: foo => i! { dg-error "been used as an external module name" } end program -! { dg-final { cleanup-modules "foo bar test test2 test3" } } diff --git a/gcc/testsuite/gfortran.dg/use_5.f90 b/gcc/testsuite/gfortran.dg/use_5.f90 index 0554f394a3b0..44f5389a381c 100644 --- a/gcc/testsuite/gfortran.dg/use_5.f90 +++ b/gcc/testsuite/gfortran.dg/use_5.f90 @@ -45,5 +45,3 @@ use z if ((.my. i) /= 2+15) call abort () if ((.addfive. i) /= 2+5) call abort () end - -! { dg-final { cleanup-modules "x y z" } } diff --git a/gcc/testsuite/gfortran.dg/use_6.f90 b/gcc/testsuite/gfortran.dg/use_6.f90 index 2be10b76bf14..0579e830f7b8 100644 --- a/gcc/testsuite/gfortran.dg/use_6.f90 +++ b/gcc/testsuite/gfortran.dg/use_6.f90 @@ -41,5 +41,3 @@ use x, only : operator(.bar.) => operator(.addfive.) ! { dg-error "Fortran 2003: use y, operator(.my.) => operator(.addfive.) ! { dg-error "Fortran 2003: Renaming operators in USE statements" } use z end - -! { dg-final { cleanup-modules "x y z" } } diff --git a/gcc/testsuite/gfortran.dg/use_7.f90 b/gcc/testsuite/gfortran.dg/use_7.f90 index 7ebd1e2bf2c3..5e0b3c7c6cec 100644 --- a/gcc/testsuite/gfortran.dg/use_7.f90 +++ b/gcc/testsuite/gfortran.dg/use_7.f90 @@ -45,5 +45,3 @@ use x, only : bar => operator(.addfive.) ! { dg-error "Syntax error in USE state use y, operator(.my.) => sub ! { dg-error "Syntax error in USE statement" } use y, operator(+) => operator(.addfive.) ! { dg-error "Syntax error in USE statement" } end - -! { dg-final { cleanup-modules "x y z" } } diff --git a/gcc/testsuite/gfortran.dg/use_9.f90 b/gcc/testsuite/gfortran.dg/use_9.f90 index 419ef47f9272..588f29dec975 100644 --- a/gcc/testsuite/gfortran.dg/use_9.f90 +++ b/gcc/testsuite/gfortran.dg/use_9.f90 @@ -13,4 +13,3 @@ end module test use test, only: operator(.func.) ! { dg-error "not found in module 'test'" } end -! { dg-final { cleanup-modules "test" } } diff --git a/gcc/testsuite/gfortran.dg/use_allocated_1.f90 b/gcc/testsuite/gfortran.dg/use_allocated_1.f90 index e590f6a95619..fb51502edc2d 100644 --- a/gcc/testsuite/gfortran.dg/use_allocated_1.f90 +++ b/gcc/testsuite/gfortran.dg/use_allocated_1.f90 @@ -16,5 +16,3 @@ subroutine init use foo if (.not.allocated(bar)) call abort end subroutine init - -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/use_iso_c_binding.f90 b/gcc/testsuite/gfortran.dg/use_iso_c_binding.f90 index 8a28490f7b2d..99323d60177e 100644 --- a/gcc/testsuite/gfortran.dg/use_iso_c_binding.f90 +++ b/gcc/testsuite/gfortran.dg/use_iso_c_binding.f90 @@ -46,5 +46,3 @@ module use_stmt_7 ! --Rickett, 09.13.06 use iso_c_binding, only: c_int, c_int end module use_stmt_7 - -! { dg-final { cleanup-modules "use_stmt_2 use_stmt_3 use_stmt_4 use_stmt_5 use_stmt_6 use_stmt_7" } } diff --git a/gcc/testsuite/gfortran.dg/use_only_1.f90 b/gcc/testsuite/gfortran.dg/use_only_1.f90 index e01324384166..c40e751c6580 100644 --- a/gcc/testsuite/gfortran.dg/use_only_1.f90 +++ b/gcc/testsuite/gfortran.dg/use_only_1.f90 @@ -89,4 +89,3 @@ contains if (yfoobar (77) /= 77_4) call abort () end subroutine END PROGRAM test2uses -! { dg-final { cleanup-modules "xmod ymod" } } diff --git a/gcc/testsuite/gfortran.dg/use_only_2.f90 b/gcc/testsuite/gfortran.dg/use_only_2.f90 index a2bfb30099f6..71db83cf7b08 100644 --- a/gcc/testsuite/gfortran.dg/use_only_2.f90 +++ b/gcc/testsuite/gfortran.dg/use_only_2.f90 @@ -27,4 +27,3 @@ end module MyMod3 module MyMod4 USE MyMod3, only: write_MyInt end module MYMOD4 -! { dg-final { cleanup-modules "mymod1 mymod2 mymod3 mymod4" } } diff --git a/gcc/testsuite/gfortran.dg/use_only_3.f90 b/gcc/testsuite/gfortran.dg/use_only_3.f90 index 509752a7ba48..b264506d4c38 100644 --- a/gcc/testsuite/gfortran.dg/use_only_3.f90 +++ b/gcc/testsuite/gfortran.dg/use_only_3.f90 @@ -32,7 +32,3 @@ subroutine dforceb(c0, i, betae, ipol, bec0, ctabin, gqq, gqqm, qmat, dq2, df) & dq2, gmes end subroutine dforceb -! { dg-final { cleanup-modules "cell_base cvan gvecs kinds" } } -! { dg-final { cleanup-modules "constants electrons_base gvecw parameters" } } -! { dg-final { cleanup-modules "control_flags electrons_nose ions_base" } } - diff --git a/gcc/testsuite/gfortran.dg/use_only_4.f90 b/gcc/testsuite/gfortran.dg/use_only_4.f90 index a37db45ef777..6a6cb067afc8 100644 --- a/gcc/testsuite/gfortran.dg/use_only_4.f90 +++ b/gcc/testsuite/gfortran.dg/use_only_4.f90 @@ -31,4 +31,3 @@ end module m2 use m2 call two end -! { dg-final { cleanup-modules "m1 m2" } } diff --git a/gcc/testsuite/gfortran.dg/use_only_5.f90 b/gcc/testsuite/gfortran.dg/use_only_5.f90 index 56d33f42750b..fb169810a4d1 100644 --- a/gcc/testsuite/gfortran.dg/use_only_5.f90 +++ b/gcc/testsuite/gfortran.dg/use_only_5.f90 @@ -34,5 +34,3 @@ module m_common_namespaces use m_common_attrs, only: dictionary_t use m_common_attrs, only: get_prefix_by_index end module m_common_namespaces - -! { dg-final { cleanup-modules "m_common_attrs m_common_namespaces" } } diff --git a/gcc/testsuite/gfortran.dg/use_rename_1.f90 b/gcc/testsuite/gfortran.dg/use_rename_1.f90 index 2e9a3c8652a2..5feda7ad40bf 100644 --- a/gcc/testsuite/gfortran.dg/use_rename_1.f90 +++ b/gcc/testsuite/gfortran.dg/use_rename_1.f90 @@ -24,4 +24,3 @@ subroutine read_initial_config_nml2() integer :: nmoltype_phase namelist /confNmoltypePhase/ nmoltype_phase end subroutine read_initial_config_nml2 -! { dg-final { cleanup-modules "common_init_conf" } } diff --git a/gcc/testsuite/gfortran.dg/use_rename_2.f90 b/gcc/testsuite/gfortran.dg/use_rename_2.f90 index 3ca6f698af58..3688bc8fd390 100644 --- a/gcc/testsuite/gfortran.dg/use_rename_2.f90 +++ b/gcc/testsuite/gfortran.dg/use_rename_2.f90 @@ -22,5 +22,3 @@ contains if (b .ne. 5) call abort () end subroutine test2 end - -! { dg-final { cleanup-modules "reduction5" } } diff --git a/gcc/testsuite/gfortran.dg/use_rename_3.f90 b/gcc/testsuite/gfortran.dg/use_rename_3.f90 index 9f28e2ee70ea..33b21e59e102 100644 --- a/gcc/testsuite/gfortran.dg/use_rename_3.f90 +++ b/gcc/testsuite/gfortran.dg/use_rename_3.f90 @@ -32,4 +32,3 @@ program main print *, 'Is flag' endif end program -! { dg-final { cleanup-modules "funcinterfacemod secondmod" } } diff --git a/gcc/testsuite/gfortran.dg/use_rename_4.f90 b/gcc/testsuite/gfortran.dg/use_rename_4.f90 index 4ce71040178f..e0e83b89181a 100644 --- a/gcc/testsuite/gfortran.dg/use_rename_4.f90 +++ b/gcc/testsuite/gfortran.dg/use_rename_4.f90 @@ -20,5 +20,3 @@ PROGRAM main CALL abort () END IF END PROGRAM main - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/use_rename_5.f90 b/gcc/testsuite/gfortran.dg/use_rename_5.f90 index 09f87c405386..3d7839a0d121 100644 --- a/gcc/testsuite/gfortran.dg/use_rename_5.f90 +++ b/gcc/testsuite/gfortran.dg/use_rename_5.f90 @@ -15,5 +15,3 @@ PROGRAM main i = 4 ! { dg-error "no IMPLICIT type" } j = 5 END PROGRAM main - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/used_before_typed_3.f90 b/gcc/testsuite/gfortran.dg/used_before_typed_3.f90 index ab1b2a91f0ae..5654d97688d8 100644 --- a/gcc/testsuite/gfortran.dg/used_before_typed_3.f90 +++ b/gcc/testsuite/gfortran.dg/used_before_typed_3.f90 @@ -37,5 +37,3 @@ END FUNCTION test4 ! Test an empty function works, too. INTEGER FUNCTION test5 () END FUNCTION test5 - -! { dg-final { cleanup-modules "testmod" } } diff --git a/gcc/testsuite/gfortran.dg/used_dummy_types_1.f90 b/gcc/testsuite/gfortran.dg/used_dummy_types_1.f90 index 0cf01bb50e29..30f3d4cdd1c8 100644 --- a/gcc/testsuite/gfortran.dg/used_dummy_types_1.f90 +++ b/gcc/testsuite/gfortran.dg/used_dummy_types_1.f90 @@ -34,5 +34,3 @@ end module atest call test (res) if (res%a.ne.42) call abort end - -! { dg-final { cleanup-modules "mtyp atest" } } diff --git a/gcc/testsuite/gfortran.dg/used_dummy_types_2.f90 b/gcc/testsuite/gfortran.dg/used_dummy_types_2.f90 index a47cabc430c4..f12d2864d0b5 100644 --- a/gcc/testsuite/gfortran.dg/used_dummy_types_2.f90 +++ b/gcc/testsuite/gfortran.dg/used_dummy_types_2.f90 @@ -30,5 +30,3 @@ contains v = x%f2(:) end subroutine foo end module mod2 - -! { dg-final { cleanup-modules "mod1 mod2" } } diff --git a/gcc/testsuite/gfortran.dg/used_dummy_types_3.f90 b/gcc/testsuite/gfortran.dg/used_dummy_types_3.f90 index c7e373a04643..5ff760842489 100644 --- a/gcc/testsuite/gfortran.dg/used_dummy_types_3.f90 +++ b/gcc/testsuite/gfortran.dg/used_dummy_types_3.f90 @@ -33,5 +33,3 @@ TYPE(data_type) :: x CALL TEST(x) ! { dg-error "Type mismatch in argument" } END - -! { dg-final { cleanup-modules "t1 t2" } } diff --git a/gcc/testsuite/gfortran.dg/used_dummy_types_4.f90 b/gcc/testsuite/gfortran.dg/used_dummy_types_4.f90 index fb36fa7bfbd6..9a627b82ccf4 100644 --- a/gcc/testsuite/gfortran.dg/used_dummy_types_4.f90 +++ b/gcc/testsuite/gfortran.dg/used_dummy_types_4.f90 @@ -98,5 +98,3 @@ contains y = seq_type3 (99) end subroutine foo END - -! { dg-final { cleanup-modules "global" } } diff --git a/gcc/testsuite/gfortran.dg/used_dummy_types_5.f90 b/gcc/testsuite/gfortran.dg/used_dummy_types_5.f90 index 2000c3271fcc..10c90c4ca69a 100644 --- a/gcc/testsuite/gfortran.dg/used_dummy_types_5.f90 +++ b/gcc/testsuite/gfortran.dg/used_dummy_types_5.f90 @@ -82,5 +82,3 @@ contains print *, x, y, z, dt2, st2, ns2, ns1 end subroutine foo END - -! { dg-final { cleanup-modules "global" } } diff --git a/gcc/testsuite/gfortran.dg/used_dummy_types_6.f90 b/gcc/testsuite/gfortran.dg/used_dummy_types_6.f90 index ea3905122305..5b1c79765ea7 100644 --- a/gcc/testsuite/gfortran.dg/used_dummy_types_6.f90 +++ b/gcc/testsuite/gfortran.dg/used_dummy_types_6.f90 @@ -43,5 +43,3 @@ MODULE P_POTENTIAL_ENERGY USE ATOMS USE CONSTRAINT, ONLY : ENERGY_CONSTRAINT END MODULE P_POTENTIAL_ENERGY - -! { dg-final { cleanup-modules "atoms constraint potential_energy p_constraint p_potential_energy" } } diff --git a/gcc/testsuite/gfortran.dg/used_dummy_types_7.f90 b/gcc/testsuite/gfortran.dg/used_dummy_types_7.f90 index b0acc51409f4..c3dea45c861d 100644 --- a/gcc/testsuite/gfortran.dg/used_dummy_types_7.f90 +++ b/gcc/testsuite/gfortran.dg/used_dummy_types_7.f90 @@ -42,4 +42,3 @@ INTERFACE END SUBROUTINE END INTERFACE END MODULE -! { dg-final { cleanup-modules "atom types list" } } diff --git a/gcc/testsuite/gfortran.dg/used_dummy_types_8.f90 b/gcc/testsuite/gfortran.dg/used_dummy_types_8.f90 index 8a966a80a533..84233841c811 100644 --- a/gcc/testsuite/gfortran.dg/used_dummy_types_8.f90 +++ b/gcc/testsuite/gfortran.dg/used_dummy_types_8.f90 @@ -32,4 +32,3 @@ END MODULE M1 D1=T1(3) write(6,*) E1(D1) END -! { dg-final { cleanup-modules "m1" } } diff --git a/gcc/testsuite/gfortran.dg/used_interface_ref.f90 b/gcc/testsuite/gfortran.dg/used_interface_ref.f90 index 10746c795ce3..1b241e976ac5 100644 --- a/gcc/testsuite/gfortran.dg/used_interface_ref.f90 +++ b/gcc/testsuite/gfortran.dg/used_interface_ref.f90 @@ -43,5 +43,3 @@ REAL :: solveCConvert(1:anzKomponenten) solveCConvert = (/(real(i), i = 1, anzKomponenten)/) END FUNCTION solveCConvert - -! { dg-final { cleanup-modules "module_conc module_thermocalc" } } diff --git a/gcc/testsuite/gfortran.dg/used_types_1.f90 b/gcc/testsuite/gfortran.dg/used_types_1.f90 index 4fbd328910eb..61356ab2c563 100644 --- a/gcc/testsuite/gfortran.dg/used_types_1.f90 +++ b/gcc/testsuite/gfortran.dg/used_types_1.f90 @@ -19,5 +19,3 @@ CONTAINS mtpcar%coo='a' !ICE was here END SUBROUTINE str_clan END MODULE - -! { dg-final { cleanup-modules "testcase tp_trace" } } diff --git a/gcc/testsuite/gfortran.dg/used_types_10.f90 b/gcc/testsuite/gfortran.dg/used_types_10.f90 index c35fb58e617e..4fbdc8e68e73 100644 --- a/gcc/testsuite/gfortran.dg/used_types_10.f90 +++ b/gcc/testsuite/gfortran.dg/used_types_10.f90 @@ -69,4 +69,3 @@ contains end subroutine foo_bar -! { dg-final { cleanup-modules "derived_type_mod tools" } } diff --git a/gcc/testsuite/gfortran.dg/used_types_11.f90 b/gcc/testsuite/gfortran.dg/used_types_11.f90 index 0cae5f171245..b3f4eaa56e4a 100644 --- a/gcc/testsuite/gfortran.dg/used_types_11.f90 +++ b/gcc/testsuite/gfortran.dg/used_types_11.f90 @@ -35,4 +35,3 @@ end subroutine bar x => foo () print *, associated (x) end -! { dg-final { cleanup-modules "a b" } } diff --git a/gcc/testsuite/gfortran.dg/used_types_12.f90 b/gcc/testsuite/gfortran.dg/used_types_12.f90 index 21d0fe2177a3..cc9870fb25b9 100644 --- a/gcc/testsuite/gfortran.dg/used_types_12.f90 +++ b/gcc/testsuite/gfortran.dg/used_types_12.f90 @@ -26,5 +26,3 @@ PROGRAM MAIN TYPE(T1) :: BAZ BAZ = BAR END -! { dg-final { cleanup-modules "m" } } - diff --git a/gcc/testsuite/gfortran.dg/used_types_13.f90 b/gcc/testsuite/gfortran.dg/used_types_13.f90 index 9208b593333f..12804fb16077 100644 --- a/gcc/testsuite/gfortran.dg/used_types_13.f90 +++ b/gcc/testsuite/gfortran.dg/used_types_13.f90 @@ -24,5 +24,3 @@ subroutine plane () call point ( gp) end subroutine plane end module gfcbug44 -! { dg-final { cleanup-modules "geo gfcbug44" } } - diff --git a/gcc/testsuite/gfortran.dg/used_types_14.f90 b/gcc/testsuite/gfortran.dg/used_types_14.f90 index 3316b4ad02ca..bc166a8d55e7 100644 --- a/gcc/testsuite/gfortran.dg/used_types_14.f90 +++ b/gcc/testsuite/gfortran.dg/used_types_14.f90 @@ -29,4 +29,3 @@ contains end subroutine foo_ext end module foo_mod -! { dg-final { cleanup-modules "foo_type_mod foo_mod" } } diff --git a/gcc/testsuite/gfortran.dg/used_types_15.f90 b/gcc/testsuite/gfortran.dg/used_types_15.f90 index 7f7dbb8e1395..885ecb1952e1 100644 --- a/gcc/testsuite/gfortran.dg/used_types_15.f90 +++ b/gcc/testsuite/gfortran.dg/used_types_15.f90 @@ -32,4 +32,3 @@ CONTAINS atom = dam%atoms%table(1) END SUBROUTINE END MODULE -! { dg-final { cleanup-modules "class_dummy_atom_types test_class_intensity_private" } } diff --git a/gcc/testsuite/gfortran.dg/used_types_16.f90 b/gcc/testsuite/gfortran.dg/used_types_16.f90 index b1ad779cff6f..f5c3108f2505 100644 --- a/gcc/testsuite/gfortran.dg/used_types_16.f90 +++ b/gcc/testsuite/gfortran.dg/used_types_16.f90 @@ -48,4 +48,3 @@ SUBROUTINE dummy_atom_list_init_copy(this, other) this%table(1:this%nused) = other%table(1:other%nused) END SUBROUTINE -! { dg-final { cleanup-modules "class_dummy_atom_types class_dummy_atom_list" } } diff --git a/gcc/testsuite/gfortran.dg/used_types_17.f90 b/gcc/testsuite/gfortran.dg/used_types_17.f90 index 964f37187886..631efaf7b77d 100644 --- a/gcc/testsuite/gfortran.dg/used_types_17.f90 +++ b/gcc/testsuite/gfortran.dg/used_types_17.f90 @@ -46,5 +46,3 @@ contains end subroutine boxarray_sort end module boxarray_module - -! { dg-final { cleanup-modules "box_module sort_box_module boxarray_module" } } diff --git a/gcc/testsuite/gfortran.dg/used_types_19.f90 b/gcc/testsuite/gfortran.dg/used_types_19.f90 index dbec8dc1c8e4..406e874c42ba 100644 --- a/gcc/testsuite/gfortran.dg/used_types_19.f90 +++ b/gcc/testsuite/gfortran.dg/used_types_19.f90 @@ -23,4 +23,3 @@ program C use A type(A_type):: A_var end program C -! { dg-final { cleanup-modules "a b" } } diff --git a/gcc/testsuite/gfortran.dg/used_types_2.f90 b/gcc/testsuite/gfortran.dg/used_types_2.f90 index b1870d12b5ae..c819f5e449a4 100644 --- a/gcc/testsuite/gfortran.dg/used_types_2.f90 +++ b/gcc/testsuite/gfortran.dg/used_types_2.f90 @@ -30,5 +30,3 @@ LOGICAL FUNCTION foobar (x) foobar = .FALSE. c = bar (x) END FUNCTION foobar -! { dg-final { cleanup-modules "types foo" } } - diff --git a/gcc/testsuite/gfortran.dg/used_types_20.f90 b/gcc/testsuite/gfortran.dg/used_types_20.f90 index c08235c67f29..272c0e8aacd9 100644 --- a/gcc/testsuite/gfortran.dg/used_types_20.f90 +++ b/gcc/testsuite/gfortran.dg/used_types_20.f90 @@ -46,4 +46,3 @@ CONTAINS TYPE(outer), INTENT(IN) :: a END SUBROUTINE test3 END MODULE test -! { dg-final { cleanup-modules "types mymod test" } } diff --git a/gcc/testsuite/gfortran.dg/used_types_22.f90 b/gcc/testsuite/gfortran.dg/used_types_22.f90 index 2a5ae451a3dc..c1d9326ddb97 100644 --- a/gcc/testsuite/gfortran.dg/used_types_22.f90 +++ b/gcc/testsuite/gfortran.dg/used_types_22.f90 @@ -290,5 +290,3 @@ subroutine smooth_mesh type(vector) :: new_pos ! the new vertex position, after smoothing end subroutine smooth_mesh -! { dg-final { cleanup-modules "class_vector class_dimensions tools_math" } } -! { dg-final { cleanup-modules "class_motion class_bc_math class_bc tools_mesh_basics" } } diff --git a/gcc/testsuite/gfortran.dg/used_types_23.f90 b/gcc/testsuite/gfortran.dg/used_types_23.f90 index 7374223693f2..71aefffaf770 100644 --- a/gcc/testsuite/gfortran.dg/used_types_23.f90 +++ b/gcc/testsuite/gfortran.dg/used_types_23.f90 @@ -26,4 +26,3 @@ module smooth_mesh type(vector ) :: new_pos ! { dg-error "used before it is defined" } end module smooth_mesh -! { dg-final { cleanup-modules "class_vector tools_math smooth_mesh" } } diff --git a/gcc/testsuite/gfortran.dg/used_types_24.f90 b/gcc/testsuite/gfortran.dg/used_types_24.f90 index 44d2f5ec1992..39eed6f2f01a 100644 --- a/gcc/testsuite/gfortran.dg/used_types_24.f90 +++ b/gcc/testsuite/gfortran.dg/used_types_24.f90 @@ -29,5 +29,3 @@ module test_mod implicit none end module test_mod - -! { dg-final { cleanup-modules "m1 m2 test_mod" } } diff --git a/gcc/testsuite/gfortran.dg/used_types_25.f90 b/gcc/testsuite/gfortran.dg/used_types_25.f90 index 35ac8c75b86e..4d10813f6f86 100644 --- a/gcc/testsuite/gfortran.dg/used_types_25.f90 +++ b/gcc/testsuite/gfortran.dg/used_types_25.f90 @@ -12,6 +12,3 @@ use m type t ! { dg-error "Derived type definition of 't' at .1. has already been defined" } end type t ! { dg-error "Expecting END PROGRAM statement" } end - -! { dg-final { cleanup-modules "m" } } - diff --git a/gcc/testsuite/gfortran.dg/used_types_26.f90 b/gcc/testsuite/gfortran.dg/used_types_26.f90 index 2c0437f63e17..8051930b72b1 100644 --- a/gcc/testsuite/gfortran.dg/used_types_26.f90 +++ b/gcc/testsuite/gfortran.dg/used_types_26.f90 @@ -18,5 +18,3 @@ use m2 type(t) :: x ! { dg-error "Type name 't' at .1. is ambiguous" } end - -! { dg-final { cleanup-modules "m m2" } } diff --git a/gcc/testsuite/gfortran.dg/used_types_3.f90 b/gcc/testsuite/gfortran.dg/used_types_3.f90 index 812db1133c6f..8273ee420ea2 100644 --- a/gcc/testsuite/gfortran.dg/used_types_3.f90 +++ b/gcc/testsuite/gfortran.dg/used_types_3.f90 @@ -55,4 +55,3 @@ ofTypB => a%ofTypA a%ofTypA(i,j) = ofTypB(k,j) end subroutine buggy end module modC -! { dg-final { cleanup-modules "moda modb modc" } } diff --git a/gcc/testsuite/gfortran.dg/used_types_4.f90 b/gcc/testsuite/gfortran.dg/used_types_4.f90 index 58877c6ab301..b8dc488a2d4f 100644 --- a/gcc/testsuite/gfortran.dg/used_types_4.f90 +++ b/gcc/testsuite/gfortran.dg/used_types_4.f90 @@ -37,4 +37,3 @@ contains call InitRECFAST(CP%omegab,CP%h0,CP%tcmb,CP%yhe) end subroutine inithermo end module ThermoData -! { dg-final { cleanup-modules "precision modelparams timesteps thermodata" } } diff --git a/gcc/testsuite/gfortran.dg/used_types_5.f90 b/gcc/testsuite/gfortran.dg/used_types_5.f90 index 427ede1efae4..7f729b8204c4 100644 --- a/gcc/testsuite/gfortran.dg/used_types_5.f90 +++ b/gcc/testsuite/gfortran.dg/used_types_5.f90 @@ -56,4 +56,3 @@ end module global if (any (x .ne. (/42.0, 42.0, -42.0, -42.0/))) call abort () if (cam%i .ne. 99) call abort () end -! { dg-final { cleanup-modules "types global" } } diff --git a/gcc/testsuite/gfortran.dg/used_types_6.f90 b/gcc/testsuite/gfortran.dg/used_types_6.f90 index 52fa55460df7..1811213b5254 100644 --- a/gcc/testsuite/gfortran.dg/used_types_6.f90 +++ b/gcc/testsuite/gfortran.dg/used_types_6.f90 @@ -34,4 +34,3 @@ CONTAINS RETURN END SUBROUTINE bar END MODULE seg_mod -! { dg-final { cleanup-modules "type_mod seg_mod" } } diff --git a/gcc/testsuite/gfortran.dg/used_types_7.f90 b/gcc/testsuite/gfortran.dg/used_types_7.f90 index 91354005d21c..1557da54b7f6 100644 --- a/gcc/testsuite/gfortran.dg/used_types_7.f90 +++ b/gcc/testsuite/gfortran.dg/used_types_7.f90 @@ -36,4 +36,3 @@ contains clock%CurrTime = clock%CurrTime + clock%CurrTime end subroutine ESMF_ClockAdvance end module foo -! { dg-final { cleanup-modules "foo bar" } } diff --git a/gcc/testsuite/gfortran.dg/used_types_8.f90 b/gcc/testsuite/gfortran.dg/used_types_8.f90 index 58d2084f3629..256b83501e8f 100644 --- a/gcc/testsuite/gfortran.dg/used_types_8.f90 +++ b/gcc/testsuite/gfortran.dg/used_types_8.f90 @@ -43,4 +43,3 @@ contains clock%CurrTime = clock%CurrTime + clock%CurrTime end subroutine ESMF_ClockAdvance end module foo -! { dg-final { cleanup-modules "foo bar" } } diff --git a/gcc/testsuite/gfortran.dg/used_types_9.f90 b/gcc/testsuite/gfortran.dg/used_types_9.f90 index fc09d155c0fc..960b0c6b21e3 100644 --- a/gcc/testsuite/gfortran.dg/used_types_9.f90 +++ b/gcc/testsuite/gfortran.dg/used_types_9.f90 @@ -33,4 +33,3 @@ contains end interface end subroutine integrate end module foo -! { dg-final { cleanup-modules "foo bar" } } diff --git a/gcc/testsuite/gfortran.dg/userdef_operator_1.f90 b/gcc/testsuite/gfortran.dg/userdef_operator_1.f90 index e8af3720afdd..bf965e5f7093 100644 --- a/gcc/testsuite/gfortran.dg/userdef_operator_1.f90 +++ b/gcc/testsuite/gfortran.dg/userdef_operator_1.f90 @@ -32,5 +32,3 @@ program opshape a = dot_product (t(:,1), t(:,2) .cross. t(:,3)) end program opshape - -! { dg-final { cleanup-modules "geometry" } } diff --git a/gcc/testsuite/gfortran.dg/userdef_operator_2.f90 b/gcc/testsuite/gfortran.dg/userdef_operator_2.f90 index 5b294c3eeda7..83392c6b6c39 100644 --- a/gcc/testsuite/gfortran.dg/userdef_operator_2.f90 +++ b/gcc/testsuite/gfortran.dg/userdef_operator_2.f90 @@ -15,5 +15,3 @@ contains print*, a .myop. b end subroutine test_fn end module test_mod - -! { dg-final { cleanup-modules "test_mod" } } diff --git a/gcc/testsuite/gfortran.dg/value_1.f90 b/gcc/testsuite/gfortran.dg/value_1.f90 index 526a028ec3a5..be459b0978a7 100644 --- a/gcc/testsuite/gfortran.dg/value_1.f90 +++ b/gcc/testsuite/gfortran.dg/value_1.f90 @@ -81,4 +81,3 @@ contains end subroutine complex_foo end program test_value -! { dg-final { cleanup-modules "global" } } diff --git a/gcc/testsuite/gfortran.dg/value_4.f90 b/gcc/testsuite/gfortran.dg/value_4.f90 index 718f9ae5cf22..473c28182d7b 100644 --- a/gcc/testsuite/gfortran.dg/value_4.f90 +++ b/gcc/testsuite/gfortran.dg/value_4.f90 @@ -81,4 +81,3 @@ program value_4 v = c_to_c (u, w) if (delta ((4.0 * u), v)) call abort () end program value_4 -! { dg-final { cleanup-modules "global" } } diff --git a/gcc/testsuite/gfortran.dg/value_6.f03 b/gcc/testsuite/gfortran.dg/value_6.f03 index 0650d3295b4e..844960fe0e74 100644 --- a/gcc/testsuite/gfortran.dg/value_6.f03 +++ b/gcc/testsuite/gfortran.dg/value_6.f03 @@ -22,4 +22,3 @@ program main implicit none call test('a') end program main -! { dg-final { cleanup-modules "pr32732" } } diff --git a/gcc/testsuite/gfortran.dg/vect/fast-math-real8-pr40801.f90 b/gcc/testsuite/gfortran.dg/vect/fast-math-real8-pr40801.f90 index 2d4018049d5e..eb6330def63e 100644 --- a/gcc/testsuite/gfortran.dg/vect/fast-math-real8-pr40801.f90 +++ b/gcc/testsuite/gfortran.dg/vect/fast-math-real8-pr40801.f90 @@ -35,4 +35,3 @@ ENDIF END SUBROUTINE ACCONV ! { dg-final { cleanup-tree-dump "vect" } } -! { dg-final { cleanup-modules "yomphy0" } } diff --git a/gcc/testsuite/gfortran.dg/vect/fast-math-vect-8.f90 b/gcc/testsuite/gfortran.dg/vect/fast-math-vect-8.f90 index a5436b740a0e..26d850de961e 100644 --- a/gcc/testsuite/gfortran.dg/vect/fast-math-vect-8.f90 +++ b/gcc/testsuite/gfortran.dg/vect/fast-math-vect-8.f90 @@ -92,4 +92,3 @@ end module solv_cap ! { dg-final { scan-tree-dump-times "vectorized 1 loops" 1 "vect" { target vect_intfloat_cvt } } } ! { dg-final { cleanup-tree-dump "vect" } } -! { dg-final { cleanup-modules "solv_cap" } } diff --git a/gcc/testsuite/gfortran.dg/vect/pr46213.f90 b/gcc/testsuite/gfortran.dg/vect/pr46213.f90 index 2eb12dd3eedc..504d1a3cf841 100644 --- a/gcc/testsuite/gfortran.dg/vect/pr46213.f90 +++ b/gcc/testsuite/gfortran.dg/vect/pr46213.f90 @@ -23,4 +23,3 @@ contains end program test ! { dg-final { cleanup-tree-dump "vect" } } -! { dg-final { cleanup-modules "foo" } } diff --git a/gcc/testsuite/gfortran.dg/vect/vect-8.f90 b/gcc/testsuite/gfortran.dg/vect/vect-8.f90 index a3ce768cc21b..c12cde19fa68 100644 --- a/gcc/testsuite/gfortran.dg/vect/vect-8.f90 +++ b/gcc/testsuite/gfortran.dg/vect/vect-8.f90 @@ -705,4 +705,3 @@ END SUBROUTINE kernel ! { dg-final { scan-tree-dump-times "vectorized 19 loops" 1 "vect" } } ! { dg-final { cleanup-tree-dump "vect" } } -! { dg-final { cleanup-modules "lfk_prec" } } diff --git a/gcc/testsuite/gfortran.dg/vect/vect-gems.f90 b/gcc/testsuite/gfortran.dg/vect/vect-gems.f90 index 66e878d3deec..019b41558446 100644 --- a/gcc/testsuite/gfortran.dg/vect/vect-gems.f90 +++ b/gcc/testsuite/gfortran.dg/vect/vect-gems.f90 @@ -55,4 +55,3 @@ END MODULE UPML_mod ! { dg-final { scan-tree-dump-times "vectorized 1 loops" 1 "vect" } } ! { dg-final { cleanup-tree-dump "vect" } } -! { dg-final { cleanup-modules "upml_mod" } } diff --git a/gcc/testsuite/gfortran.dg/vector_subscript_bound_1.f90 b/gcc/testsuite/gfortran.dg/vector_subscript_bound_1.f90 index 00e31f9595ff..f4328504f24d 100644 --- a/gcc/testsuite/gfortran.dg/vector_subscript_bound_1.f90 +++ b/gcc/testsuite/gfortran.dg/vector_subscript_bound_1.f90 @@ -17,5 +17,3 @@ CONTAINS PRINT *, pw%cr(UBOUND(pw%cr)) END SUBROUTINE pw_write END MODULE - -! { dg-final { cleanup-modules "pw_types" } } diff --git a/gcc/testsuite/gfortran.dg/volatile10.f90 b/gcc/testsuite/gfortran.dg/volatile10.f90 index 2065b164cadf..47356d9ba482 100644 --- a/gcc/testsuite/gfortran.dg/volatile10.f90 +++ b/gcc/testsuite/gfortran.dg/volatile10.f90 @@ -146,4 +146,3 @@ end program main ! TODO: dg-final { scan-tree-dump-not "main_test2_3" "optimized" } ! { dg-final { scan-tree-dump "main_test2_4" "optimized" } } ! { dg-final { cleanup-tree-dump "optimized" } } -! { dg-final { cleanup-modules "impl one two" } } diff --git a/gcc/testsuite/gfortran.dg/volatile5.f90 b/gcc/testsuite/gfortran.dg/volatile5.f90 index 42607a1e63ed..57a4c898eba5 100644 --- a/gcc/testsuite/gfortran.dg/volatile5.f90 +++ b/gcc/testsuite/gfortran.dg/volatile5.f90 @@ -40,4 +40,3 @@ end program main ! { dg-final { scan-tree-dump-not "cPresent" "optimized" } } ! { dg-final { scan-tree-dump-not "cStillPresent" "optimized" } } ! { dg-final { cleanup-tree-dump "optimized" } } -! { dg-final { cleanup-modules "volmod" } } diff --git a/gcc/testsuite/gfortran.dg/volatile9.f90 b/gcc/testsuite/gfortran.dg/volatile9.f90 index e7cba6b07240..41be085c54d5 100644 --- a/gcc/testsuite/gfortran.dg/volatile9.f90 +++ b/gcc/testsuite/gfortran.dg/volatile9.f90 @@ -40,5 +40,3 @@ implicit none volatile :: v13 end subroutine s14 - -! { dg-final { cleanup-modules "mod13 mod13a mod13b" } } diff --git a/gcc/testsuite/gfortran.dg/warn_function_without_result_2.f90 b/gcc/testsuite/gfortran.dg/warn_function_without_result_2.f90 index 25fd0b73a75a..64f6eb68759b 100644 --- a/gcc/testsuite/gfortran.dg/warn_function_without_result_2.f90 +++ b/gcc/testsuite/gfortran.dg/warn_function_without_result_2.f90 @@ -16,4 +16,3 @@ contains k = 8 end function j end module m -! { dg-final { cleanup-modules "mod" } } diff --git a/gcc/testsuite/gfortran.dg/warn_implicit_procedure_1.f90 b/gcc/testsuite/gfortran.dg/warn_implicit_procedure_1.f90 index 8f21b60e9c2d..3f907c78d5bc 100644 --- a/gcc/testsuite/gfortran.dg/warn_implicit_procedure_1.f90 +++ b/gcc/testsuite/gfortran.dg/warn_implicit_procedure_1.f90 @@ -39,5 +39,3 @@ PROGRAM main ! Can't check undefined function, because it needs to be declared a type ! in any case (and the implicit type is enough to not trigger this warning). END PROGRAM - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/warn_intent_out_not_set.f90 b/gcc/testsuite/gfortran.dg/warn_intent_out_not_set.f90 index 76c62eaec346..22bef8ce7c1c 100644 --- a/gcc/testsuite/gfortran.dg/warn_intent_out_not_set.f90 +++ b/gcc/testsuite/gfortran.dg/warn_intent_out_not_set.f90 @@ -26,5 +26,3 @@ CONTAINS type(t2), intent(out) :: x END SUBROUTINE END MODULE - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/warn_unused_var_2.f90 b/gcc/testsuite/gfortran.dg/warn_unused_var_2.f90 index 7eccc6e6c1f5..5dcf4991d244 100644 --- a/gcc/testsuite/gfortran.dg/warn_unused_var_2.f90 +++ b/gcc/testsuite/gfortran.dg/warn_unused_var_2.f90 @@ -15,5 +15,3 @@ program main j = 1 print*,"j=",j end program main - -! { dg-final { cleanup-modules "util_mod" } } diff --git a/gcc/testsuite/gfortran.dg/warn_unused_var_3.f90 b/gcc/testsuite/gfortran.dg/warn_unused_var_3.f90 index 86a888321f7a..9bc7f0ba398e 100644 --- a/gcc/testsuite/gfortran.dg/warn_unused_var_3.f90 +++ b/gcc/testsuite/gfortran.dg/warn_unused_var_3.f90 @@ -11,5 +11,3 @@ program main use util_mod, only: i ! { dg-warning "Unused parameter .i. which has been explicitly imported" } integer, parameter :: j = 4 ! { dg-warning "Unused parameter .j. declared at" } end program main - -! { dg-final { cleanup-modules "util_mod" } } diff --git a/gcc/testsuite/gfortran.dg/where_operator_assign_1.f90 b/gcc/testsuite/gfortran.dg/where_operator_assign_1.f90 index c2b4abf85189..bc4790ae719a 100644 --- a/gcc/testsuite/gfortran.dg/where_operator_assign_1.f90 +++ b/gcc/testsuite/gfortran.dg/where_operator_assign_1.f90 @@ -104,5 +104,3 @@ CONTAINS END FUNCTION iaef END PROGRAM test_prog - -! { dg-final { cleanup-modules "kind_mod pointer_mod" } } diff --git a/gcc/testsuite/gfortran.dg/where_operator_assign_2.f90 b/gcc/testsuite/gfortran.dg/where_operator_assign_2.f90 index 420103f1978e..52fbd276f6ff 100644 --- a/gcc/testsuite/gfortran.dg/where_operator_assign_2.f90 +++ b/gcc/testsuite/gfortran.dg/where_operator_assign_2.f90 @@ -102,5 +102,3 @@ contains endwhere end subroutine test_where_4 end program test -! { dg-final { cleanup-modules "global" } } - diff --git a/gcc/testsuite/gfortran.dg/where_operator_assign_3.f90 b/gcc/testsuite/gfortran.dg/where_operator_assign_3.f90 index eddbdfc00aff..d1b5e37c8a5b 100644 --- a/gcc/testsuite/gfortran.dg/where_operator_assign_3.f90 +++ b/gcc/testsuite/gfortran.dg/where_operator_assign_3.f90 @@ -77,5 +77,3 @@ contains endwhere end subroutine test_where_char2 end program test -! { dg-final { cleanup-modules "global" } } - diff --git a/gcc/testsuite/gfortran.dg/where_operator_assign_4.f90 b/gcc/testsuite/gfortran.dg/where_operator_assign_4.f90 index e1c479e5f938..74ce1ba6ad39 100644 --- a/gcc/testsuite/gfortran.dg/where_operator_assign_4.f90 +++ b/gcc/testsuite/gfortran.dg/where_operator_assign_4.f90 @@ -28,4 +28,3 @@ END WHERE WHERE (I(:)%I>0) J=I ! { dg-error "Non-ELEMENTAL user-defined assignment in WHERE" } END -! { dg-final { cleanup-modules "m1" } } diff --git a/gcc/testsuite/gfortran.dg/whole_file_11.f90 b/gcc/testsuite/gfortran.dg/whole_file_11.f90 index d50e48107048..d01b2100c4be 100644 --- a/gcc/testsuite/gfortran.dg/whole_file_11.f90 +++ b/gcc/testsuite/gfortran.dg/whole_file_11.f90 @@ -35,5 +35,3 @@ FUNCTION foo_count() USE module_foo, ONLY: foo INTEGER :: foo_count END FUNCTION - -! { dg-final { cleanup-modules "module_foo" } } diff --git a/gcc/testsuite/gfortran.dg/whole_file_14.f90 b/gcc/testsuite/gfortran.dg/whole_file_14.f90 index 65058960b957..030e8cd14592 100644 --- a/gcc/testsuite/gfortran.dg/whole_file_14.f90 +++ b/gcc/testsuite/gfortran.dg/whole_file_14.f90 @@ -25,4 +25,3 @@ contains j%this => base !to one another end subroutine check !take j out of scope end program test_equi -! { dg-final { cleanup-modules "global" } } diff --git a/gcc/testsuite/gfortran.dg/whole_file_15.f90 b/gcc/testsuite/gfortran.dg/whole_file_15.f90 index 08d6120445b8..9988757cb1b6 100644 --- a/gcc/testsuite/gfortran.dg/whole_file_15.f90 +++ b/gcc/testsuite/gfortran.dg/whole_file_15.f90 @@ -29,4 +29,3 @@ CONTAINS SUBROUTINE ep_force_release() END SUBROUTINE ep_force_release END MODULE ep_types -! { dg-final { cleanup-modules "replica_types ep_types" } } diff --git a/gcc/testsuite/gfortran.dg/whole_file_19.f90 b/gcc/testsuite/gfortran.dg/whole_file_19.f90 index 56f3cb69d8f4..cd69f92d427a 100644 --- a/gcc/testsuite/gfortran.dg/whole_file_19.f90 +++ b/gcc/testsuite/gfortran.dg/whole_file_19.f90 @@ -22,4 +22,3 @@ END MODULE USE M CALL b() END -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/whole_file_20.f03 b/gcc/testsuite/gfortran.dg/whole_file_20.f03 index 61e2a4df9d84..766851776bf2 100644 --- a/gcc/testsuite/gfortran.dg/whole_file_20.f03 +++ b/gcc/testsuite/gfortran.dg/whole_file_20.f03 @@ -29,5 +29,3 @@ SUBROUTINE polymorph(b) USE classtype CLASS(t) :: b END SUBROUTINE - -! { dg-final { cleanup-modules "classtype" } } diff --git a/gcc/testsuite/gfortran.dg/whole_file_21.f90 b/gcc/testsuite/gfortran.dg/whole_file_21.f90 index ec9256a77298..b1c1dacb2dd2 100644 --- a/gcc/testsuite/gfortran.dg/whole_file_21.f90 +++ b/gcc/testsuite/gfortran.dg/whole_file_21.f90 @@ -23,5 +23,3 @@ CONTAINS END SUBROUTINE four END MODULE mod END - -! { dg-final { cleanup-modules "mod" } } diff --git a/gcc/testsuite/gfortran.dg/whole_file_22.f90 b/gcc/testsuite/gfortran.dg/whole_file_22.f90 index d833491f0d88..69e8107d63cf 100644 --- a/gcc/testsuite/gfortran.dg/whole_file_22.f90 +++ b/gcc/testsuite/gfortran.dg/whole_file_22.f90 @@ -35,5 +35,3 @@ subroutine test() USE M CALL b() END - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/whole_file_23.f90 b/gcc/testsuite/gfortran.dg/whole_file_23.f90 index c8f66e6cd62a..3fd1051fe30c 100644 --- a/gcc/testsuite/gfortran.dg/whole_file_23.f90 +++ b/gcc/testsuite/gfortran.dg/whole_file_23.f90 @@ -45,5 +45,3 @@ program xjoin character (len=5) :: words(2) = (/"two ","three"/) write (*,"(1x,'words = ',a)") "'"//join (words, "&")//"'" end program xjoin - -! { dg-final { cleanup-modules "util_mod" } } diff --git a/gcc/testsuite/gfortran.dg/whole_file_24.f90 b/gcc/testsuite/gfortran.dg/whole_file_24.f90 index 4ac11cce2fd3..3ff6ca85700f 100644 --- a/gcc/testsuite/gfortran.dg/whole_file_24.f90 +++ b/gcc/testsuite/gfortran.dg/whole_file_24.f90 @@ -31,5 +31,3 @@ contains end subroutine syntax_init_from_ifile end module syntax_rules end - -! { dg-final { cleanup-modules "iso_red ifiles syntax_rules" } } diff --git a/gcc/testsuite/gfortran.dg/whole_file_25.f90 b/gcc/testsuite/gfortran.dg/whole_file_25.f90 index d2cbd36ae1d6..8eaa5a5e4b53 100644 --- a/gcc/testsuite/gfortran.dg/whole_file_25.f90 +++ b/gcc/testsuite/gfortran.dg/whole_file_25.f90 @@ -17,5 +17,3 @@ end module ints USE INTS CALL NOZZLE () END program CORTESA - -! { dg-final { cleanup-modules "ints" } } diff --git a/gcc/testsuite/gfortran.dg/whole_file_26.f90 b/gcc/testsuite/gfortran.dg/whole_file_26.f90 index 8ce45107086b..eec09453babf 100644 --- a/gcc/testsuite/gfortran.dg/whole_file_26.f90 +++ b/gcc/testsuite/gfortran.dg/whole_file_26.f90 @@ -22,5 +22,3 @@ subroutine VALUE() end subroutine VALUE end - -! { dg-final { cleanup-modules "ints" } } diff --git a/gcc/testsuite/gfortran.dg/whole_file_27.f90 b/gcc/testsuite/gfortran.dg/whole_file_27.f90 index 412954727316..48362c6f0b41 100644 --- a/gcc/testsuite/gfortran.dg/whole_file_27.f90 +++ b/gcc/testsuite/gfortran.dg/whole_file_27.f90 @@ -206,5 +206,3 @@ program d_coo_err stop end program d_coo_err - -! { dg-final { cleanup-modules "base_mat_mod const_mod d_base_mat_mod" } } diff --git a/gcc/testsuite/gfortran.dg/whole_file_33.f90 b/gcc/testsuite/gfortran.dg/whole_file_33.f90 index 31faeaa09927..4163b77a4bc1 100644 --- a/gcc/testsuite/gfortran.dg/whole_file_33.f90 +++ b/gcc/testsuite/gfortran.dg/whole_file_33.f90 @@ -46,5 +46,3 @@ MODULE DENSEOP x=x_o END SUBROUTINE GEINV8 END MODULE DENSEOP - -! { dg-final { cleanup-modules "la_precision lapack90 denseop" } } diff --git a/gcc/testsuite/gfortran.dg/whole_file_35.f90 b/gcc/testsuite/gfortran.dg/whole_file_35.f90 index 46a886551456..e52a2c42dd80 100644 --- a/gcc/testsuite/gfortran.dg/whole_file_35.f90 +++ b/gcc/testsuite/gfortran.dg/whole_file_35.f90 @@ -24,5 +24,3 @@ use m print *,ichar('~') ! must print "1" end program p - -! { dg-final { cleanup-modules "m" } } diff --git a/gcc/testsuite/gfortran.dg/widechar_5.f90 b/gcc/testsuite/gfortran.dg/widechar_5.f90 index ed2f32fbd09b..ece1e4d9cc79 100644 --- a/gcc/testsuite/gfortran.dg/widechar_5.f90 +++ b/gcc/testsuite/gfortran.dg/widechar_5.f90 @@ -55,5 +55,3 @@ program test_modules if (any (len_trim (outer4) /= [len(outer4), 3])) call abort end program test_modules - -! { dg-final { cleanup-modules "kinds inner middle outer" } } diff --git a/gcc/testsuite/gfortran.dg/widechar_6.f90 b/gcc/testsuite/gfortran.dg/widechar_6.f90 index 9151adba418f..799db608bb58 100644 --- a/gcc/testsuite/gfortran.dg/widechar_6.f90 +++ b/gcc/testsuite/gfortran.dg/widechar_6.f90 @@ -60,5 +60,3 @@ program test if (len (cut(4_"12345")) /= 2 .or. cut(4_"45") /= 4_"") call abort end program test - -! { dg-final { cleanup-modules "mod" } }