绑定到 C 接口的过程#
c_associated#
名称#
c_associated(3) - [ISO_C_BINDING] C 指针的状态
概要#
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
特性#
c_ptr_1 是 c_ptr 或 c_funptr 类型的标量。
c_ptr_2 与 c_ptr_1 类型相同。
返回值为逻辑类型
描述#
c_associated(3) 确定 C 指针 c_ptr_1 的状态,或者 c_ptr_1 是否与目标 c_ptr_2 关联。
选项#
- c_ptr_1
要测试是否为 C NULL 指针的 C 指针,或者在存在时测试是否指向与 c_ptr_2 相同的关联。
- c_ptr_2
要测试与 c_ptr_1 共享关联的 C 指针
结果#
返回值为逻辑类型;如果 c_ptr_1 是 C NULL 指针,或者 c_ptr1 和 c_ptr_2 指向不同的地址,则为.false.。
示例#
示例程序
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
标准#
Fortran 2003
另请参见#
c_loc(3),c_funloc(3),iso_c_binding(3)
fortran-lang 内在函数描述
c_f_pointer#
名称#
c_f_pointer(3) - [ISO_C_BINDING] 将 C 转换为 Fortran 指针
概要#
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(:)
特性#
Fortran 指针 fprt 必须与 cptr 可互操作。
仅当 fptr 为数组时才指定 shape。
描述#
c_f_pointer(3) 将目标(C 指针 cptr)分配给 Fortran 指针 fptr,并在 fptr 指向数组时指定其形状。
选项#
- cptr
c_ptr 类型的标量。它是 intent(in)。
- fptr
与 cptr 可互操作的指针。它是 intent(out)。
- shape
(可选) 类型为整数且 intent(in) 的一维数组。当且仅当 fptr 为数组时,它才存在。大小必须等于 fptr 的秩。
示例#
示例程序
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
标准#
Fortran 2003
另请参见#
c_loc(3),c_f_procpointer(3),iso_c_binding(3)
fortran-lang 内在函数描述
c_f_procpointer#
名称#
c_f_procpointer(3) - [ISO_C_BINDING] 将 C 转换为 Fortran 过程指针
概要#
call c_f_procpointer(cptr, fptr)
subroutine c_f_procpointer(cptr, fptr )
type(c_funptr),intent(in) :: cprt
type(TYPE),pointer,intent(out) :: fprt
特性#
描述#
c_f_procpointer(3) 将 C 函数指针 cptr 的目标分配给 Fortran 过程指针 fptr。
选项#
- cptr
c_funptr 类型的标量。它是 intent(in)。
- fptr
与 cptr 可互操作的过程指针。它是 intent(out)。
示例#
示例程序
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
标准#
Fortran 2003
另请参见#
c_loc(3),c_f_pointer(3),iso_c_binding(3)
fortran-lang 内在函数描述
c_funloc#
名称#
c_funloc(3) - [ISO_C_BINDING] 获取过程的 C 地址
概要#
result = c_funloc(x)
特性#
描述#
c_funloc(3) 确定参数的 C 地址。
选项#
- x
可互操作的函数或指向此类函数的指针。
结果#
返回值为 c_funptr 类型,包含参数的 C 地址。
示例#
示例程序
! 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
标准#
Fortran 2003
另请参见#
c_associated(3),c_loc(3),c_f_pointer(3),
c_f_procpointer(3),iso_c_binding(3)
fortran-lang 内在函数描述
c_loc#
名称#
c_loc(3) - [ISO_C_BINDING] 获取对象的 C 地址
概要#
result = c_loc(x)
特性#
描述#
c_loc(3) 确定参数的 C 地址。
选项#
- x
必须具有指针或目标属性。它不能是协索引对象。它要么是具有可互操作类型和种类类型参数的变量,要么是没有任何长度类型参数的标量非多态变量。
结果#
返回值为 c_ptr 类型,包含参数的 C 地址。
示例#
示例程序
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
标准#
Fortran 2003
另请参见#
c_associated(3),c_funloc(3),c_f_pointer(3),
c_f_procpointer(3),iso_c_binding(3)
fortran-lang 内在函数描述
c_sizeof#
名称#
c_sizeof(3) - [ISO_C_BINDING] 表达式的字节大小
概要#
result = c_sizeof(x)
特性#
描述#
c_sizeof(3) 计算表达式 x 占用的存储字节数。
选项#
- x
参数必须是可互操作的数据实体。
结果#
返回值为整数类型,并具有系统相关的种类 csize_t(来自 iso_c_binding 模块)。其值为参数占用的字节数。如果参数具有指针属性,则返回指向的存储区域的字节数。如果参数为派生类型,且具有指针或可分配组件,则返回值不考虑这些组件指向的数据的大小。
示例#
示例程序
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
结果
T
除非您使用的平台中默认实数变量的填充方式异常,否则该示例将打印.true.。
标准#
Fortran 2008
另请参见#
fortran-lang 内在函数描述