mirror of git://gcc.gnu.org/git/gcc.git
Remove now redundant manual cleanup-modules directive.
2012-05-15 Bernhard Reutner-Fischer <aldot@gcc.gnu.org> * gfortran.dg/*.f90: Remove now redundant manual cleanup-modules directive. From-SVN: r187521
This commit is contained in:
parent
c8957aae63
commit
2d858ed91f
|
@ -1,3 +1,8 @@
|
|||
2012-05-15 Bernhard Reutner-Fischer <aldot@gcc.gnu.org>
|
||||
|
||||
* gfortran.dg/*.f90: Remove now redundant manual
|
||||
cleanup-modules directive.
|
||||
|
||||
2012-05-14 Uros Bizjak <ubizjak@gmail.com>
|
||||
|
||||
* gcc.target/i386/avx256-unaligned-load-[1234].c: Update scan strings.
|
||||
|
|
|
@ -11,4 +11,3 @@ MODULE m
|
|||
END TYPE t ! { dg-error "END MODULE" }
|
||||
|
||||
END MODULE m
|
||||
! { dg-final { cleanup-modules "m" } }
|
||||
|
|
|
@ -11,4 +11,3 @@ MODULE m
|
|||
END TYPE error_t ! { dg-error "END MODULE" }
|
||||
|
||||
END MODULE m
|
||||
! { dg-final { cleanup-modules "m" } }
|
||||
|
|
|
@ -49,4 +49,3 @@ CONTAINS
|
|||
END SUBROUTINE impl
|
||||
|
||||
END MODULE m
|
||||
! { dg-final { cleanup-modules "m" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -43,4 +43,3 @@ CONTAINS
|
|||
END SUBROUTINE test
|
||||
|
||||
END MODULE m
|
||||
! { dg-final { cleanup-modules "m" } }
|
||||
|
|
|
@ -50,4 +50,3 @@ SUBROUTINE bottom_c(obj)
|
|||
! other stuff
|
||||
END SUBROUTINE bottom_c
|
||||
end module
|
||||
! { dg-final { cleanup-modules "m" } }
|
||||
|
|
|
@ -15,4 +15,3 @@ module ice_module
|
|||
end type c_type
|
||||
end module ice_module
|
||||
|
||||
! { dg-final { cleanup-modules "ice_module" } }
|
||||
|
|
|
@ -25,5 +25,3 @@ abstract interface
|
|||
end subroutine generic_desc
|
||||
end interface
|
||||
end module factory_pattern
|
||||
|
||||
! { dg-final { cleanup-modules "factory_pattern" } }
|
||||
|
|
|
@ -15,4 +15,3 @@ module mod
|
|||
integer, private :: z ! Fortran 2003
|
||||
end type
|
||||
end module
|
||||
! { dg-final { cleanup-modules "mod" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -31,4 +31,3 @@ program user
|
|||
bint = 8
|
||||
write(*,*) aint
|
||||
end program
|
||||
! { dg-final { cleanup-modules "base a b c" } }
|
||||
|
|
|
@ -78,5 +78,3 @@ contains
|
|||
end subroutine option_stopwatch_a
|
||||
|
||||
end program main
|
||||
! { dg-final { cleanup-modules "global my_module" } }
|
||||
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -69,4 +69,3 @@ function proc_ext (arg, chr)
|
|||
proc_ext = arg
|
||||
chr = "proc_ext"
|
||||
end function
|
||||
! { dg-final { cleanup-modules "m" } }
|
|
@ -161,4 +161,3 @@ contains
|
|||
get_d = d
|
||||
end function get_d
|
||||
end program test
|
||||
! { dg-final { cleanup-modules "foo" } }
|
||||
|
|
|
@ -51,5 +51,3 @@ contains
|
|||
CALL foobar (x)
|
||||
end subroutine bar
|
||||
END subroutine test
|
||||
|
||||
! { dg-final { cleanup-modules "m m2" } }
|
||||
|
|
|
@ -21,5 +21,3 @@ function func2()
|
|||
end function
|
||||
|
||||
end module foo
|
||||
|
||||
! { dg-final { cleanup-modules "foo" } }
|
||||
|
|
|
@ -57,5 +57,3 @@ program tao_program
|
|||
deallocate (u%design, u%model)
|
||||
deallocate (s%u)
|
||||
end program
|
||||
|
||||
! { dg-final { cleanup-modules "test_struct" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
||||
|
|
|
@ -51,5 +51,3 @@ program VST28
|
|||
call abort ()
|
||||
end if
|
||||
end program VST28
|
||||
|
||||
! { dg-final { cleanup-modules "iso_varying_string" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
||||
|
|
|
@ -43,5 +43,3 @@ program tsave
|
|||
if (info .ne. 10) call abort ()
|
||||
|
||||
end program tsave
|
||||
|
||||
! { dg-final { cleanup-modules "bar_mod" } }
|
||||
|
|
|
@ -30,4 +30,3 @@ contains
|
|||
type(d_sparse_mat), intent(out) :: a
|
||||
end subroutine bug14
|
||||
end
|
||||
! { dg-final { cleanup-modules "d_mat_mod " } }
|
||||
|
|
|
@ -18,4 +18,3 @@ module cell
|
|||
return
|
||||
end subroutine cell_output
|
||||
end module cell
|
||||
! { dg-final { cleanup-modules "cell" } }
|
||||
|
|
|
@ -68,4 +68,3 @@ contains
|
|||
end subroutine p_bld
|
||||
|
||||
end program foo
|
||||
! { dg-final { cleanup-modules "p_type_mod" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -46,5 +46,3 @@ contains
|
|||
bar = carg(1:12)
|
||||
end function
|
||||
end
|
||||
|
||||
! { dg-final { cleanup-modules "m" } }
|
||||
|
|
|
@ -15,4 +15,3 @@ program fred
|
|||
use fred1
|
||||
use fred2
|
||||
end program fred
|
||||
! { dg-final { cleanup-modules "fred1 fred2" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -29,5 +29,3 @@ program hum
|
|||
call foo(q)
|
||||
|
||||
end program hum
|
||||
|
||||
! { dg-final { cleanup-modules "moo" } }
|
||||
|
|
|
@ -74,4 +74,3 @@ contains
|
|||
if(associated(p)) deallocate(p)
|
||||
end subroutine sub
|
||||
end module test
|
||||
! { dg-final { cleanup-modules "test" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -42,4 +42,3 @@ program test
|
|||
20 continue
|
||||
if (i /= -1) call abort ()
|
||||
end
|
||||
! { dg-final { cleanup-modules "arswitch" } }
|
||||
|
|
|
@ -30,6 +30,3 @@ END MODULE
|
|||
CALL ABORT()
|
||||
2 CONTINUE
|
||||
END
|
||||
|
||||
! { dg-final { cleanup-modules "tt" } }
|
||||
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -28,6 +28,3 @@ contains
|
|||
end subroutine myRoutine ! this is not ambiguous !
|
||||
|
||||
end module
|
||||
|
||||
! { dg-final { cleanup-modules "a1 a2 b" } }
|
||||
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -39,4 +39,3 @@ END PROGRAM P
|
|||
SUBROUTINE bar (arg)
|
||||
EXTERNAL arg
|
||||
END SUBROUTINE bar
|
||||
! { dg-final { cleanup-modules "m1 m2" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -26,4 +26,3 @@ program test
|
|||
if (astr(i:i) /= achar(0)) call abort
|
||||
end do
|
||||
end program test
|
||||
! { dg-final { cleanup-modules "cyclic" } }
|
||||
|
|
|
@ -18,5 +18,3 @@ CONTAINS
|
|||
if (present (j1)) stop
|
||||
end subroutine
|
||||
END MODULE s_TESTS
|
||||
|
||||
! { dg-final { cleanup-modules "m s_tests" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -25,4 +25,3 @@ program len_test
|
|||
|
||||
write(*,*) my_string(x)
|
||||
end program len_test
|
||||
! { dg-final { cleanup-modules "test" } }
|
||||
|
|
|
@ -15,5 +15,3 @@ MODULE WinData
|
|||
! { dg-error "specification expression" "" { target *-*-* } 13 }
|
||||
END TYPE TWindowData
|
||||
END MODULE WinData
|
||||
|
||||
! { dg-final { cleanup-modules "windata" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -25,5 +25,3 @@ CONTAINS
|
|||
lenf = x(1)
|
||||
end function lenf
|
||||
END MODULE B1
|
||||
|
||||
! { dg-final { cleanup-modules "b1" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -27,5 +27,3 @@ end module bar
|
|||
call xmain
|
||||
if (c(1) .ne. "ab") call abort
|
||||
end
|
||||
! { dg-final { cleanup-modules "bar" } }
|
||||
|
||||
|
|
|
@ -46,5 +46,3 @@ contains
|
|||
REAL,INTENT(IN) :: b(:,:)
|
||||
END SUBROUTINE
|
||||
end module m3
|
||||
|
||||
! { dg-final { cleanup-modules "m1 m2 m3" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -48,4 +48,3 @@ PROGRAM main
|
|||
END PROGRAM main
|
||||
|
||||
! { dg-excess-errors "Syntex error in IF" }
|
||||
! { dg-final { cleanup-modules "m" } }
|
||||
|
|
|
@ -31,5 +31,3 @@ contains
|
|||
if (.not. associated (a, b)) call abort()
|
||||
end subroutine cmpPtr
|
||||
end
|
||||
|
||||
! { dg-final { cleanup-modules "m" } }
|
||||
|
|
|
@ -77,4 +77,3 @@ end function not_OK
|
|||
|
||||
END
|
||||
|
||||
! { dg-final { cleanup-modules "m1" } }
|
||||
|
|
|
@ -33,5 +33,3 @@ contains
|
|||
integer, intent(in) :: x
|
||||
end function assumed_len
|
||||
end program main
|
||||
|
||||
! { dg-final { cleanup-modules "funcs mod2" } }
|
||||
|
|
|
@ -42,5 +42,3 @@ contains
|
|||
x (2) = 21.0
|
||||
END SUBROUTINE roo
|
||||
end program test
|
||||
|
||||
! { dg-final { cleanup-modules "global" } }
|
||||
|
|
|
@ -22,5 +22,3 @@ CONTAINS
|
|||
write(6,*) I
|
||||
END SUBROUTINE TST
|
||||
END
|
||||
|
||||
! { dg-final { cleanup-modules "addon" } }
|
||||
|
|
|
@ -43,5 +43,3 @@ end module mod1
|
|||
call foo (bar, i)
|
||||
if (i .ne. 2) call abort ()
|
||||
end
|
||||
|
||||
! { dg-final { cleanup-modules "mod1" } }
|
||||
|
|
|
@ -14,5 +14,3 @@ CONTAINS
|
|||
END MODULE TEST
|
||||
|
||||
end
|
||||
|
||||
! { dg-final { cleanup-modules "test" } }
|
||||
|
|
|
@ -52,5 +52,3 @@ contains
|
|||
call MPI_Send2(x, 1, 1,1,1,j,i)
|
||||
end
|
||||
end
|
||||
|
||||
! { dg-final { cleanup-modules "mpi_interface" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -53,5 +53,3 @@ contains
|
|||
end subroutine a
|
||||
|
||||
end program oh_no_not_pr15908_again
|
||||
|
||||
! { dg-final { cleanup-modules "global" } }
|
||||
|
|
|
@ -23,5 +23,3 @@ program TestStringTools
|
|||
if (txt .ne. "AaBbCcDdEeFfGgHhIiJjKkLlMmNnOoPpQqRrSsTtUuVvWwXxYyZz") &
|
||||
call abort ()
|
||||
end program TestStringTools
|
||||
|
||||
! { dg-final { cleanup-modules "chtest" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -18,4 +18,3 @@ END MODULE M1
|
|||
USE M1
|
||||
CALL S1(2)
|
||||
END
|
||||
! { dg-final { cleanup-modules "m1" } }
|
||||
|
|
|
@ -14,5 +14,3 @@ contains
|
|||
init = x
|
||||
end function init
|
||||
end module sd
|
||||
|
||||
! { dg-final { cleanup-modules "sd" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -59,5 +59,3 @@ contains
|
|||
end if
|
||||
end subroutine sub0
|
||||
end module bind_c_dts_2
|
||||
|
||||
! { dg-final { cleanup-modules "bind_c_dts_2" } }
|
||||
|
|
|
@ -35,5 +35,3 @@ contains
|
|||
end if
|
||||
end subroutine sub0
|
||||
end module bind_c_dts_3
|
||||
|
||||
! { dg-final { cleanup-modules "bind_c_dts_3" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -50,5 +50,3 @@ PROGRAM main
|
|||
write (*,*) liter_cb(link_info)
|
||||
|
||||
END PROGRAM main
|
||||
|
||||
! { dg-final { cleanup-modules "liter_cb_mod" } }
|
||||
|
|
|
@ -9,5 +9,3 @@ contains
|
|||
i = 0
|
||||
end subroutine sub0
|
||||
end module bind_c_implicit_vars
|
||||
|
||||
! { dg-final { cleanup-modules "bind_c_implicit_vars" } }
|
||||
|
|
|
@ -19,4 +19,3 @@ module d
|
|||
implicit none
|
||||
bind(c) :: a ! { dg-error "applied to" }
|
||||
end module d
|
||||
! { dg-final { cleanup-modules "a" } }
|
||||
|
|
|
@ -35,5 +35,3 @@ contains
|
|||
end function my_f03_func
|
||||
|
||||
end module bind_c_procs
|
||||
|
||||
! { dg-final { cleanup-modules "bind_c_procs" } }
|
||||
|
|
|
@ -71,5 +71,3 @@ contains
|
|||
func4ent = -88.0
|
||||
end function func4
|
||||
end module mod
|
||||
|
||||
! { dg-final { cleanup-modules "mod" } }
|
||||
|
|
|
@ -27,5 +27,3 @@ program main
|
|||
call gen(x)
|
||||
if(x /= 17) call abort()
|
||||
end program main
|
||||
|
||||
! { dg-final { cleanup-modules "mod" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -21,5 +21,3 @@ contains
|
|||
liter_cb = 0
|
||||
END FUNCTION liter_cb
|
||||
end module m
|
||||
|
||||
! { dg-final { cleanup-modules "m" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
||||
|
|
|
@ -36,5 +36,3 @@ contains
|
|||
end subroutine changeF90Globals
|
||||
|
||||
end module bind_c_vars
|
||||
|
||||
! { dg-final { cleanup-modules "bind_c_vars" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -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" } }
|
||||
|
|
|
@ -13,5 +13,3 @@ end interface
|
|||
|
||||
call my_c_print()
|
||||
end program main
|
||||
|
||||
! { dg-final { cleanup-modules "a" } }
|
||||
|
|
Some files were not shown because too many files have changed in this diff Show More
Loading…
Reference in New Issue