Procedures for binding to C interfaces

c_associated

Name

c_associated(3) - [ISO_C_BINDING] Status of a C pointer

Synopsis

    result = c_associated(c_prt_1, [c_ptr_2] )
     logical function c_associated(c_prt_1, cptr_2)

      TYPE,intent(in) ::c_ptr_1
      TYPE,intent(in),optional ::c_ptr_2

Characteristics

  • c_ptr_1 is a scalar of the type c_ptr or c_funptr.

  • c_ptr_2 is a scalar of the same type as c_ptr_1.

  • The return value is of type logical

Description

c_associated(3) determines the status of the C pointer c_ptr_1 or if c_ptr_1 is associated with the target c_ptr_2.

Options

  • c_ptr_1

    C pointer to test for being a C NULL pointer, or to test if pointing to the same association as c_ptr_2 when present.

  • c_ptr_2

    C pointer to test for shared association with c_ptr_1

Result

The return value is of type logical; it is .false. if either c_ptr_1 is a C NULL pointer or if c_ptr1 and c_ptr_2 point to different addresses.

Examples

Sample program:

program demo_c_associated

contains

subroutine association_test(a,b)
use iso_c_binding, only: c_associated, c_loc, c_ptr
implicit none
real, pointer :: a
type(c_ptr) :: b
   if(c_associated(b, c_loc(a))) &
      stop 'b and a do not point to same target'
end subroutine association_test

end program demo_c_associated

Standard

Fortran 2003

See Also

c_loc(3), c_funloc(3), iso_c_binding(3)

fortran-lang intrinsic descriptions

c_f_pointer

Name

c_f_pointer(3) - [ISO_C_BINDING] Convert C into Fortran pointer

Synopsis

    call c_f_pointer(cptr, fptr [,shape] )
     subroutine c_f_pointer(cptr, fptr ,shape )

      type(c_ptr),intent(in) :: cprt
      type(TYPE),pointer,intent(out) :: fprt
      integer,intent(in),optional :: shape(:)

Characteristics

The Fortran pointer fprt must be interoperable with cptr

shape is only specified if fptr is an array.

Description

c_f_pointer(3) assigns the target (the C pointer cptr) to the Fortran pointer fptr and specifies its shape if fptr points to an array.

Options

  • cptr

    scalar of the type c_ptr. It is intent(in).

  • fptr

    pointer interoperable with cptr. it is intent(out).

  • shape

    (Optional) Rank-one array of type integer with intent(in) . It shall be present if and only if fptr is an array. The size must be equal to the rank of fptr.

Examples

Sample program:

program demo_c_f_pointer
use iso_c_binding
implicit none
interface
   subroutine my_routine(p) bind(c,name='myC_func')
      import :: c_ptr
      type(c_ptr), intent(out) :: p
   end subroutine
end interface
type(c_ptr) :: cptr
real,pointer :: a(:)
   call my_routine(cptr)
   call c_f_pointer(cptr, a, [12])
end program demo_c_f_pointer

Standard

Fortran 2003

See Also

c_loc(3), c_f_procpointer(3), iso_c_binding(3)

fortran-lang intrinsic descriptions

c_f_procpointer

Name

c_f_procpointer(3) - [ISO_C_BINDING] Convert C into Fortran procedure pointer

Synopsis

    call c_f_procpointer(cptr, fptr)
     subroutine c_f_procpointer(cptr, fptr )

      type(c_funptr),intent(in) :: cprt
      type(TYPE),pointer,intent(out) :: fprt

Characteristics

Description

c_f_procpointer(3) assigns the target of the C function pointer cptr to the Fortran procedure pointer fptr.

Options

  • cptr

    scalar of the type c_funptr. It is intent(in).

  • fptr

    procedure pointer interoperable with cptr. It is intent(out).

Examples

Sample program:

program demo_c_f_procpointer
use iso_c_binding
implicit none
abstract interface
   function func(a)
   import :: c_float
   real(c_float), intent(in) :: a
   real(c_float) :: func
   end function
end interface
interface
   function getIterFunc() bind(c,name="getIterFunc")
   import :: c_funptr
   type(c_funptr) :: getIterFunc
   end function
end interface
type(c_funptr) :: cfunptr
procedure(func), pointer :: myFunc
   cfunptr = getIterFunc()
   call c_f_procpointer(cfunptr, myFunc)
end program demo_c_f_procpointer

Standard

Fortran 2003

See Also

c_loc(3), c_f_pointer(3), iso_c_binding(3)

fortran-lang intrinsic descriptions

c_funloc

Name

c_funloc(3) - [ISO_C_BINDING] Obtain the C address of a procedure

Synopsis

    result = c_funloc(x)

Characteristics

Description

c_funloc(3) determines the C address of the argument.

Options

  • x

    Interoperable function or pointer to such function.

Result

The return value is of type c_funptr and contains the C address of the argument.

Examples

Sample program:

! program demo_c_funloc and module
module x
use iso_c_binding
implicit none
contains
subroutine sub(a) bind(c)
real(c_float) :: a
   a = sqrt(a)+5.0
end subroutine sub
end module x
!
program demo_c_funloc
use iso_c_binding
use x
implicit none
interface
   subroutine my_routine(p) bind(c,name='myC_func')
     import :: c_funptr
     type(c_funptr), intent(in) :: p
   end subroutine
end interface
   call my_routine(c_funloc(sub))
!
end program demo_c_funloc

Standard

Fortran 2003

See Also

c_associated(3), c_loc(3), c_f_pointer(3),

c_f_procpointer(3), iso_c_binding(3)

fortran-lang intrinsic descriptions

c_loc

Name

c_loc(3) - [ISO_C_BINDING] Obtain the C address of an object

Synopsis

    result = c_loc(x)

Characteristics

Description

c_loc(3) determines the C address of the argument.

Options

  • x

    Shall have either the pointer or target attribute. It shall not be a coindexed object. It shall either be a variable with interoperable type and kind type parameters, or be a scalar, nonpolymorphic variable with no length type parameters.

Result

The return value is of type c_ptr and contains the C address of the argument.

Examples

Sample program:

   subroutine association_test(a,b)
   use iso_c_binding, only: c_associated, c_loc, c_ptr
   implicit none
   real, pointer :: a
   type(c_ptr) :: b
     if(c_associated(b, c_loc(a))) &
        stop 'b and a do not point to same target'
   end subroutine association_test

Standard

Fortran 2003

See Also

c_associated(3), c_funloc(3), c_f_pointer(3),

c_f_procpointer(3), iso_c_binding(3)

fortran-lang intrinsic descriptions

c_sizeof

Name

c_sizeof(3) - [ISO_C_BINDING] Size in bytes of an expression

Synopsis

    result = c_sizeof(x)

Characteristics

Description

c_sizeof(3) calculates the number of bytes of storage the expression x occupies.

Options

  • x

    The argument shall be an interoperable data entity.

Result

The return value is of type integer and of the system-dependent kind csize_t (from the iso_c_binding module). Its value is the number of bytes occupied by the argument. If the argument has the pointer attribute, the number of bytes of the storage area pointed to is returned. If the argument is of a derived type with pointer or allocatable components, the return value does not account for the sizes of the data pointed to by these components.

Examples

Sample program:

program demo_c_sizeof
use iso_c_binding
implicit none
real(c_float) :: r, s(5)
   print *, (c_sizeof(s)/c_sizeof(r) == 5)
end program demo_c_sizeof

Results:

    T

The example will print .true. unless you are using a platform where default real variables are unusually padded.

Standard

Fortran 2008

See Also

storage_size(3)

fortran-lang intrinsic descriptions