1! { dg-do run }
2! { dg-additional-sources c_f_pointer_complex_driver.c }
3! { dg-options "-std=gnu -w" }
4! Test c_f_pointer for the different types of interoperable complex values.
5module c_f_pointer_complex
6  use, intrinsic :: iso_c_binding, only: c_float_complex, c_double_complex, &
7       c_long_double_complex, c_f_pointer, c_ptr, c_long_double, c_int
8  implicit none
9
10contains
11  subroutine test_complex_scalars(my_c_float_complex, my_c_double_complex, &
12       my_c_long_double_complex) bind(c)
13    type(c_ptr), value :: my_c_float_complex
14    type(c_ptr), value :: my_c_double_complex
15    type(c_ptr), value :: my_c_long_double_complex
16    complex(c_float_complex), pointer :: my_f03_float_complex
17    complex(c_double_complex), pointer :: my_f03_double_complex
18    complex(c_long_double_complex), pointer :: my_f03_long_double_complex
19
20    call c_f_pointer(my_c_float_complex, my_f03_float_complex)
21    call c_f_pointer(my_c_double_complex, my_f03_double_complex)
22    call c_f_pointer(my_c_long_double_complex, my_f03_long_double_complex)
23
24    if(my_f03_float_complex /= (1.0, 0.0)) STOP 1
25    if(my_f03_double_complex /= (2.0d0, 0.0d0)) STOP 2
26    if(my_f03_long_double_complex /= (3.0_c_long_double, &
27         0.0_c_long_double)) STOP 3
28  end subroutine test_complex_scalars
29
30  subroutine test_complex_arrays(float_complex_array, double_complex_array, &
31       long_double_complex_array, num_elems) bind(c)
32    type(c_ptr), value :: float_complex_array
33    type(c_ptr), value :: double_complex_array
34    type(c_ptr), value :: long_double_complex_array
35    complex(c_float_complex), pointer, dimension(:) :: f03_float_complex_array
36    complex(c_double_complex), pointer, dimension(:) :: &
37         f03_double_complex_array
38    complex(c_long_double_complex), pointer, dimension(:) :: &
39         f03_long_double_complex_array
40    integer(c_int), value :: num_elems
41    integer :: i
42
43    call c_f_pointer(float_complex_array, f03_float_complex_array, &
44         (/ num_elems /))
45    call c_f_pointer(double_complex_array, f03_double_complex_array, &
46         (/ num_elems /))
47    call c_f_pointer(long_double_complex_array, &
48         f03_long_double_complex_array, (/ num_elems /))
49
50    do i = 1, num_elems
51       if(f03_float_complex_array(i) &
52            /= (i*(1.0, 0.0))) STOP 4
53       if(f03_double_complex_array(i) &
54            /= (i*(1.0d0, 0.0d0))) STOP 5
55       if(f03_long_double_complex_array(i) &
56            /= (i*(1.0_c_long_double, 0.0_c_long_double))) STOP 6
57    end do
58  end subroutine test_complex_arrays
59end module c_f_pointer_complex
60