nvptx, libgfortran: Switch out of "minimal" mode
[official-gcc.git] / gcc / testsuite / gfortran.dg / pr89943_3.f90
blob84a9fb74741767812d1d0c09fe0ec5ca54690f1d
1 ! { dg-do compile }
2 module Foo_mod
4 implicit none
6 interface
7 module subroutine runFoo4C(ndim) bind(C, name="runFoo")
8 use, intrinsic :: iso_c_binding
9 implicit none
10 integer(c_int32_t) , intent(in) :: ndim
11 end subroutine runFoo4C
12 end interface
14 contains
16 end module Foo_mod
18 submodule(Foo_mod) Foo_smod
20 contains
22 module subroutine runFoo4C(ndim) bind(C, name="runFu") ! { dg-error "Mismatch in BIND" }
23 use, intrinsic :: iso_c_binding ! { dg-error "Unexpected USE statement" }
24 implicit none ! { dg-error "Unexpected IMPLICIT NONE statement" }
25 integer(c_int32_t) , intent(in) :: ndim ! { dg-error "Symbol 'c_int32_t' at .1. has no IMPLICIT type" }
26 end subroutine runFoo4C ! { dg-error " Expecting END SUBMODULE" }
28 end submodule Foo_smod