OSDN Git Service

PR target/35944
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / bind_c_dts_2.f03
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
6
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
12
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
18
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
31
32     if (my_type%my_nested_type%i .ne. expected_i) then
33        call abort ()
34     end if
35
36     if (.not. c_associated(my_type%my_nested_type%nested_c_address, &
37          expected_nested_c_address)) then
38        call abort ()
39     end if
40
41     if (my_type%my_nested_type%array(1) .ne. expected_array_1) then
42        call abort ()
43     end if
44
45     if (my_type%my_nested_type%array(2) .ne. expected_array_2) then
46        call abort ()
47     end if
48
49     if (my_type%my_nested_type%array(3) .ne. expected_array_3) then
50        call abort ()
51     end if
52
53     if (.not. c_associated(my_type%c_address, expected_c_address)) then
54        call abort ()
55     end if
56
57     if (my_type%j .ne. expected_j) then
58        call abort ()
59     end if
60   end subroutine sub0
61 end module bind_c_dts_2
62
63 ! { dg-final { cleanup-modules "bind_c_dts_2" } }