RISC-V: Regenerate opt urls.
[official-gcc.git] / gcc / testsuite / gfortran.dg / bind_c_dts_2.f03
blobfc77d1e2a45badb7d9182346b03d1aa8cde9ee55
1 ! { dg-do run }
2 ! { dg-additional-sources bind_c_dts_2_driver.c }
3 module bind_c_dts_2
4 use, intrinsic :: iso_c_binding
5 implicit none
7 type, bind(c) :: my_c_type_0
8    integer(c_int) :: i
9    type(c_ptr) :: nested_c_address
10    integer(c_int) :: array(3)
11 end type my_c_type_0
13 type, bind(c) :: my_c_type_1
14    type(my_c_type_0) :: my_nested_type
15    type(c_ptr) :: c_address
16    integer(c_int) :: j
17 end type my_c_type_1
19 contains
20   subroutine sub0(my_type, expected_i, expected_nested_c_address, &
21        expected_array_1, expected_array_2, expected_array_3, &
22        expected_c_address, expected_j) bind(c)
23     type(my_c_type_1) :: my_type
24     integer(c_int), value :: expected_i
25     type(c_ptr), value :: expected_nested_c_address
26     integer(c_int), value :: expected_array_1
27     integer(c_int), value :: expected_array_2
28     integer(c_int), value :: expected_array_3
29     type(c_ptr), value :: expected_c_address
30     integer(c_int), value :: expected_j
32     if (my_type%my_nested_type%i .ne. expected_i) then
33        STOP 1
34     end if
36     if (.not. c_associated(my_type%my_nested_type%nested_c_address, &
37          expected_nested_c_address)) then
38        STOP 2
39     end if
41     if (my_type%my_nested_type%array(1) .ne. expected_array_1) then
42        STOP 3
43     end if
45     if (my_type%my_nested_type%array(2) .ne. expected_array_2) then
46        STOP 4
47     end if
49     if (my_type%my_nested_type%array(3) .ne. expected_array_3) then
50        STOP 5
51     end if
53     if (.not. c_associated(my_type%c_address, expected_c_address)) then
54        STOP 6
55     end if
57     if (my_type%j .ne. expected_j) then
58        STOP 7
59     end if
60   end subroutine sub0
61 end module bind_c_dts_2