aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/binding_label_tests_25.f90
blob: 0769eb05de1f8b52e54d29d4aee07c7ab099addc (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
! { dg-do compile }
!
! PR fortran/48858
! PR fortran/55465
!
! Seems to be regarded as valid, even if it is doubtful
!


module m_odbc_if
  implicit none

  interface sql_set_env_attr
    function sql_set_env_attr_int( input_handle,attribute,value,length ) &
                                   result(res) bind(C,name="SQLSetEnvAttr")
      use, intrinsic :: iso_c_binding
      implicit none
      type(c_ptr), value :: input_handle
      integer(c_int), value :: attribute
      integer(c_int), value :: value  ! <<<< HERE: int passed by value (int with ptr address)
      integer(c_int), value :: length      
      integer(c_short) :: res
    end function
    function sql_set_env_attr_ptr( input_handle,attribute,value,length ) &
                                   result(res) bind(C,name="SQLSetEnvAttr")
      use, intrinsic :: iso_c_binding
      implicit none
      type(c_ptr), value :: input_handle
      integer(c_int), value :: attribute
      type(c_ptr), value :: value ! <<< HERE: "void *" (pointer address)
      integer(c_int), value :: length      
      integer(c_short) :: res
    end function
  end interface
end module

module graph_partitions
  use,intrinsic :: iso_c_binding

  interface Cfun
     subroutine cfunc1 (num, array) bind(c, name="Cfun")
       import :: c_int
       integer(c_int),value :: num
       integer(c_int)       :: array(*) ! <<< HERE: int[]
     end subroutine cfunc1

     subroutine cfunf2 (num, array) bind(c, name="Cfun")
       import :: c_int, c_ptr
       integer(c_int),value :: num
       type(c_ptr),value    :: array ! <<< HERE: void*
     end subroutine cfunf2
  end interface
end module graph_partitions

program test
  use graph_partitions
  integer(c_int) :: a(100)

  call Cfun (1, a)
  call Cfun (2, C_NULL_PTR)
end program test