arm: Add .type and .size to __gnu_cmse_nonsecure_call [PR115360]
[official-gcc.git] / gcc / testsuite / gfortran.dg / bind_c_usage_24.f90
bloba3167a5672190a0ed890a0ab4ee7ac4117de8345
1 ! { dg-do run }
2 ! { dg-additional-sources bind_c_usage_24_c.c }
4 ! PR fortran/48858
5 ! PR fortran/48820
7 ! TS 29113: BIND(C) with OPTIONAL
9 module m
10 use iso_c_binding
11 interface
12 subroutine c_proc (is_present, var) bind(C)
13 import
14 logical(c_bool), value :: is_present
15 integer(c_int), optional :: var
16 end subroutine
17 end interface
18 contains
19 subroutine subtest (is_present, var) bind(C)
20 logical(c_bool), intent(in), value :: is_present
21 integer(c_int), intent(inout), optional :: var
22 if (is_present) then
23 if (.not. present (var)) STOP 1
24 if (var /= 43) STOP 2
25 var = -45
26 else
27 if (present (var)) STOP 3
28 end if
29 end subroutine subtest
30 end module m
32 program test
33 use m
34 implicit none
35 integer :: val
37 val = 4
38 call c_proc (.false._c_bool)
39 call c_proc (.true._c_bool, val)
40 if (val /= 7) STOP 4
41 end program test