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

INTENT() on C_PTR - What's the target?

ereisch
New Contributor II
722 Views

I have a C function that would be defined as:

void my_memcpy( void *d, void *s, size_t l ) {
    memcpy( d, s, l );
}

And I am defining the interface for this as:

SUBROUTINE MEMCPY( DEST, SRC, BYTES ) BIND(C, NAME='my_memcpy')
  USE, INTRINSIC :: ISO_C_BINDING, ONLY: C_PTR, C_SIZE_T
  IMPLICIT NONE
  TYPE(C_PTR), INTENT(OUT) :: DEST
  TYPE(C_PTR), INTENT(IN) :: SRC
  INTEGER(KIND=C_SIZE_T), INTENT(IN) :: BYTES
  !DIR$ ATTRIBUTES VALUE :: DEST, SRC, BYTES
END SUBROUTINE MEMCPY

 My question is, am I using the correct INTENT attribute for the DEST and SRC arguments?  In other words, does the INTENT modifier apply to the C_PTR itself, or the target of the C_PTR?

The implementation in this case would be:

TYPE(C_PTR) :: TEMP_LOC1, TEMP_LOC2
TYPE(SOMETHING), TARGET :: FOO
TYPE(ELSE), TARGET :: BAR
TEMP_LOC1 = C_LOC( FOO )
TEMP_LOC2 = C_LOC( BAR )
CALL MEMCPY( TEMP_LOC2, TEMP_LOC1, 12345 )

 

0 Kudos
1 Solution
Steve_Lionel
Honored Contributor III
704 Views

First, from Fortran's perspective, a thing of type C_PTR does not have a target - it is not a Fortran POINTER. So, INTENT relates to whether the C_PTR can be changed, irrespective of what it is the address of.

The same applies, however, for Fortran POINTERs. This was (and still is) a source of much debate among the standards committee. As it stands today, INTENT for POINTERs relates to the pointer itself, not the target. There is an open work item for the next standard revision to do "something" about pointer intent, but no specific proposal has been introduced so far.

View solution in original post

0 Kudos
3 Replies
Steve_Lionel
Honored Contributor III
705 Views

First, from Fortran's perspective, a thing of type C_PTR does not have a target - it is not a Fortran POINTER. So, INTENT relates to whether the C_PTR can be changed, irrespective of what it is the address of.

The same applies, however, for Fortran POINTERs. This was (and still is) a source of much debate among the standards committee. As it stands today, INTENT for POINTERs relates to the pointer itself, not the target. There is an open work item for the next standard revision to do "something" about pointer intent, but no specific proposal has been introduced so far.

0 Kudos
FortranFan
Honored Contributor II
668 Views

@ereisch ,

TYPE(C_PTR), nominally an encapsulation for the C address of 'DEST', cannot be in an undefined state upon invocation of 'MY_MEMCPY', but that is what INTENT(OUT) signifies.  So that's inconsistent and your program does not conform.

Separately you may not want to check with Intel's documentation and support whether the !DIR$ ATTRIBUTES for VALUE is consistent with the value semantics of C when BIND(C) is in effect.  There is the Fortran standard option of VALUE.

But then INTENT(OUT) and VALUE don't go together either.

Perhaps you're looking for generic interfaces?

0 Kudos
jimdempseyatthecove
Honored Contributor III
652 Views

FPP is your friend:

!  MEMCPY.f90 
module foo
    INTERFACE
    SUBROUTINE MEMCPY_BYTES( DEST, SRC, NUMBYTES ) BIND(C, NAME='memcpy') ! C runtime library routine, replace with your my_memcpy
      USE, INTRINSIC :: ISO_C_BINDING, ONLY: C_PTR, C_SIZE_T
      IMPLICIT NONE
      TYPE(C_PTR) :: DEST
      TYPE(C_PTR) :: SRC
      INTEGER(KIND=C_SIZE_T) :: NUMBYTES
      !DIR$ ATTRIBUTES VALUE :: DEST, SRC, NUMBYTES
    END SUBROUTINE MEMCPY_BYTES
    END INTERFACE
end module foo
    
program MEMCPY_EXAMPLE
      USE, INTRINSIC :: ISO_C_BINDING, ONLY: C_LOC, C_SIZE_T
    use foo
    implicit none
#define MEMCPY(dest, src, n) MEMCPY_BYTES( C_LOC(dest), C_LOC(src), INT(n,KIND=C_SIZE_T))
    real :: src(10)
    real :: dest(10)
    integer :: i
    do i=1,10
        src(i) = i
    end do
    call MEMCPY(dest, src, sizeof(src))
    print *, src
    print *, dest
end program MEMCPY_EXAMPLE
   1.000000       2.000000       3.000000       4.000000       5.000000
   6.000000       7.000000       8.000000       9.000000       10.00000
   1.000000       2.000000       3.000000       4.000000       5.000000
   6.000000       7.000000       8.000000       9.000000       10.00000

Jim Dempsey

0 Kudos
Reply