Procedimentos para vincular à interfaces C#
c_associated#
Nome#
c_associated(3) - [ISO_C_BINDING] Status de um ponteiro C
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
Descrição#
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.
Opções#
- 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
Resultado#
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.
Exemplos#
Exemplo de programa:
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
Padrão#
Fortran 2003
Veja Também#
c_loc(3), c_funloc(3), iso_c_binding(3)
fortran-lang intrinsic descriptions
c_f_pointer#
Nome#
c_f_pointer(3) - [ISO_C_BINDING] Converte um ponteiro C em ponteiro Fortran
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.
Descrição#
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.
Opções#
- cptr
escalar do tipo c_ptr. É intent(in).
- fptr
ponteiro interoperável com cptr. É intent(out).
- shape
(Opcional) matriz de primeira ordem do tipo integer com intent(in). Será presente se e somente se fptr for uma matriz. O tamanho deve ser igual à ordem de fptr.
Exemplos#
Exemplo de programa:
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
Padrão#
Fortran 2003
Veja Também#
c_loc(3), c_f_procpointer(3), iso_c_binding(3)
fortran-lang intrinsic descriptions
c_f_procpointer#
Nome#
c_f_procpointer(3) - [ISO_C_BINDING] Converte C em ponteiro de procedimento Fortran
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#
Descrição#
c_f_procpointer(3) assigns the target of the C function pointer cptr to the Fortran procedure pointer fptr.
Opções#
- cptr
escalar do tipo c_funptr. É intent(in).
- fptr
ponteiro de procedimento interoperável com cptr. É intent(out).
Exemplos#
Exemplo de programa:
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
Padrão#
Fortran 2003
Veja Também#
c_loc(3), c_f_pointer(3), iso_c_binding(3)
fortran-lang intrinsic descriptions
c_funloc#
Nome#
c_funloc(3) - [ISO_C_BINDING] Obtém o endereço C de um procedimento
Synopsis#
result = c_funloc(x)
Characteristics#
Descrição#
c_funloc(3) determines the C address of the argument.
Opções#
- x
Função interoperável ou ponteiro para tal função.
Resultado#
O valor retornado é do tipo c_funptr e contém o endereço C do argumento.
Exemplos#
Exemplo de programa:
! 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
Padrão#
Fortran 2003
Veja Também#
c_associated(3), c_loc(3), c_f_pointer(3),
c_f_procpointer(3), iso_c_binding(3)
fortran-lang intrinsic descriptions
c_loc#
Nome#
c_loc(3) - [ISO_C_BINDING] Obtém o endereço C de um objeto
Synopsis#
result = c_loc(x)
Characteristics#
Descrição#
c_loc(3) determines the C address of the argument.
Opções#
- 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.
Resultado#
The return value is of type c_ptr and contains the C address of the argument.
Exemplos#
Exemplo de programa:
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
Padrão#
Fortran 2003
Veja Também#
c_associated(3), c_funloc(3), c_f_pointer(3),
c_f_procpointer(3), iso_c_binding(3)
fortran-lang intrinsic descriptions
c_sizeof#
Nome#
c_sizeof(3) - [ISO_C_BINDING] Size in bytes of an expression
Synopsis#
result = c_sizeof(x)
Characteristics#
Descrição#
c_sizeof(3) calculates the number of bytes of storage the expression x occupies.
Opções#
- x
The argument shall be an interoperable data entity.
Resultado#
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.
Exemplos#
Exemplo de programa:
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
Resultados:
T
The example will print .true. unless you are using a platform where default real variables are unusually padded.
Padrão#
Fortran 2008
Veja Também#
fortran-lang intrinsic descriptions