2 ! { dg-options "-Wno-c-binding-type" }
3 ! { dg-require-visibility "" }
5 ! That's a copy of "bind_c_usage_8.f03", "bind_c_dts_4.f03",
6 ! "bind_c_implicit_vars.f03" and "c_kind_tests_2.f03"
7 ! to check that with -Wno-c-binding-type no warning is printed.
10 MODULE ISO_C_UTILITIES
13 CHARACTER(C_CHAR
), DIMENSION(1), SAVE, TARGET
, PRIVATE
:: dummy_string
="?"
15 FUNCTION C_F_STRING(CPTR
) RESULT(FPTR
)
16 use, intrinsic :: iso_c_binding
17 TYPE(C_PTR
), INTENT(IN
) :: CPTR
! The C address
18 CHARACTER(KIND
=C_CHAR
), DIMENSION(:), POINTER :: FPTR
20 FUNCTION strlen(string
) RESULT(len
) BIND(C
,NAME
="strlen")
22 TYPE(C_PTR
), VALUE
:: string
! A C pointer
25 CALL C_F_POINTER(FPTR
=FPTR
, CPTR
=CPTR
, SHAPE
=[strlen(CPTR
)])
27 END MODULE ISO_C_UTILITIES
30 use iso_c_binding
, only
: c_int
34 type(foo
), bind(c
) :: cp
37 module bind_c_implicit_vars
42 subroutine sub0(i
) bind(c
)
45 end module bind_c_implicit_vars
48 use, intrinsic :: iso_c_binding
50 integer, parameter :: myF
= c_float
51 real(myF
), bind(c
) :: myCFloat
52 integer(myF
), bind(c
) :: myCInt
! { dg-warning "is for type REAL" }
53 integer(c_double
), bind(c
) :: myCInt2
! { dg-warning "is for type REAL" }
55 integer, parameter :: myI
= c_int
56 real(myI
) :: myReal
! { dg-warning "is for type INTEGER" }
57 real(myI
), bind(c
) :: myCFloat2
! { dg-warning "is for type INTEGER" }
58 real(4), bind(c
) :: myFloat
59 end module c_kind_tests_2