Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.

Learning to use ISO_C_BINDING

Daniel_P_4
Beginner
2,291 Views
Can someone tell me why this code does not work? I'm trying to use C_PTR to allocation (and later to reallocate) arrays with rank > 1.

Thanks,

Dan


>>>>>>>>>code starts here<<<<<<<<<<<<<<

!-------------------------------------------------------------
MODULE trans_settings
USE ISO_C_BINDING
IMPLICIT NONE
INTEGER,PARAMETER::isize0=4
INTEGER,PARAMETER::rsize0=8
INTEGER,PARAMETER::isysize=4 !4 for 32bit, 8 for 64bit
END MODULE trans_settings

!-------------------------------------------------------------
MODULE iso
USE trans_settings
IMPLICIT NONE
INTERFACE
! cray pointer style
FUNCTION trans_malloc(size) RESULT(addr)
USE trans_settings
IMPLICIT NONE
INTEGER(isize0),INTENT(IN)::size
INTEGER(isysize)::addr
END FUNCTION trans_malloc
! iso_c_binding style
FUNCTION tr_malloc(size) RESULT(addr)
USE trans_settings
IMPLICIT NONE
INTEGER(isize0),INTENT(IN)::size
TYPE(C_PTR)::addr
END FUNCTION tr_malloc
END INTERFACE
END MODULE iso

!-------------------------------------------------------------
PROGRAM main
IMPLICIT NONE
CALL testiso
END PROGRAM main

!-------------------------------------------------------------
SUBROUTINE testiso
USE iso
IMPLICIT NONE

! iso_c_binding pointer style
REAL(rsize0),DIMENSION(:,:),POINTER::riso
TYPE(C_PTR)::cp
! Cray pointer style
REAL(rsize0),DIMENSION(1)::rv
POINTER(ptr_rv,rv)

!locals
INTEGER(isize0)::i,j,irows=12,jcols=7

! iso_c_binding pointer style
cp=tr_malloc(rsize0*irows*jcols)
CALL C_F_POINTER(cp,riso,[irows,jcols])

! Cray pointer style
!ptr_rv=trans_malloc(rsize0*irows*jcols)

DO j=1,jcols
DO i=1,irows
riso(i,j)=100*i+j
END DO
END DO
END SUBROUTINE testiso

!-------------------------------------------------------------
! cray pointer style
FUNCTION trans_malloc(size) RESULT(addr)
!MALLOC wrapper
USE trans_settings
IMPLICIT NONE
INTEGER(isize0),INTENT(IN)::size
INTEGER(isysize)::addr
addr=MALLOC(size)
END FUNCTION trans_malloc

!-------------------------------------------------------------
! iso_c_binding pointer style
FUNCTION tr_malloc(size) RESULT(addr)
!MALLOC wrapper
USE trans_settings
IMPLICIT NONE
INTEGER(isize0),INTENT(IN)::size
INTEGER(isysize)::iptr
TYPE(C_PTR)::addr
iptr=MALLOC(size)
!how do I achieve addr%ptr = iptr???
addr=C_LOC(iptr)
END FUNCTION tr_malloc
0 Kudos
1 Solution
Steven_L_Intel1
Employee
2,291 Views
Note that C_PTR is a private type - you can't access its component. You can use TRANSFER both ways.

As for "universality" - it is a F2003 feature, and implementors who have been serious about F2003 tend to already have at least this part of it implemented. Intel, IBM, Sun and Cray all support this, as do (I think) gfortran and g95. I have no idea what is happening on HP-UX. You'll have to research the other compilers you're interested in.

View solution in original post

0 Kudos
7 Replies
Steven_L_Intel1
Employee
2,291 Views
This is wrong:

addr=C_LOC(iptr)

What you are getting here is the address of the routine local variable iptr, not its contents. The result is that the loop in the caller overwrites other storage.

What you want instead is:

addr = TRANSFER(iptr,addr)

This effectively converts or casts iptr to the desired C_PTR type.

I would also recommend using KIND constants from ISO_C_BINDING rather than hardcoding values.
0 Kudos
Daniel_P_4
Beginner
2,291 Views
This is wrong:

addr=C_LOC(iptr)

What you are getting here is the address of the routine local variable iptr, not its contents. The result is that the loop in the caller overwrites other storage.

What you want instead is:

addr = TRANSFER(iptr,addr)

This effectively converts or casts iptr to the desired C_PTR type.

I would also recommend using KIND constants from ISO_C_BINDING rather than hardcoding values.
Steve,

Thanks once again.

That gets me across another hurdle.

Are the operations inverses of each other?

iptr = cptr%ptr
cptr = TRANSFER(iptr,cptr)

Can you comment on the universality of ISO_C_BINDING across other, current Fortran compilers. My web searches seem to tell me this is F2003 standard. How universal can I expect it to be in F90 and F95?

Thanks again,

Dan

0 Kudos
Steven_L_Intel1
Employee
2,292 Views
Note that C_PTR is a private type - you can't access its component. You can use TRANSFER both ways.

As for "universality" - it is a F2003 feature, and implementors who have been serious about F2003 tend to already have at least this part of it implemented. Intel, IBM, Sun and Cray all support this, as do (I think) gfortran and g95. I have no idea what is happening on HP-UX. You'll have to research the other compilers you're interested in.
0 Kudos
Daniel_P_4
Beginner
2,291 Views
Note that C_PTR is a private type - you can't access its component. You can use TRANSFER both ways.

As for "universality" - it is a F2003 feature, and implementors who have been serious about F2003 tend to already have at least this part of it implemented. Intel, IBM, Sun and Cray all support this, as do (I think) gfortran and g95. I have no idea what is happening on HP-UX. You'll have to research the other compilers you're interested in.

Steve,

How silly is this idea? - to "homegrow" my own ISO_C_BINDING that might be universal across all the compilers? I guess making a C_PTR is really the easy part, eh? I think the C_F_POINTER() is the thing that is really crucial to me.

Thanks for all the help,

Dan


0 Kudos
Steven_L_Intel1
Employee
2,291 Views
C_F_POINTER is one of the harder items - it requires knowledge of how the implementation represents pointers and also a way to get the compiler to relax restrictions on type, kind and rank matching. If you have that information, it is feasible, but not "universal" in that the implementation would vary by compiler.
0 Kudos
Daniel_P_4
Beginner
2,291 Views
C_F_POINTER is one of the harder items - it requires knowledge of how the implementation represents pointers and also a way to get the compiler to relax restrictions on type, kind and rank matching. If you have that information, it is feasible, but not "universal" in that the implementation would vary by compiler.
I looked at iso_c_binding.f90 and I sort of understand what I'm seeing. I was hoping to find something that didn't require F2003 statements, but I found IMPORT and BIND(C).

I'd really like to use this C_PTR method if I can, since it clearly does what I want done, with some elegance.

Is there another way without going through a subroutine interface? Basically, I have to (1) allocate space through a c-style pointer, and (2) be able to address this space in the form of rank1, rank2, or rank3 fortran arrays, and (3) resize the arrays if needed.

Is there any F95 compliant way to make the c pointers talk to the f pointers?

Thanks again,

Dan


0 Kudos
Steven_L_Intel1
Employee
2,291 Views
There's no F95 way to do this. I can't think of a way to get what you want without going through the mess you wanted to avoid initially.
0 Kudos
Reply