Pointer Arithmetic

I’m working on a project where I need to do some pointer arithmetic. My initial investigations would seem to suggest that it is highly likely that it is possible to assume that type(c_ptr) and integer(c_intptr_t) are exactly the same representation. I.e. that the following two programs would be considered effectively equivalent.

program pointer_math
  use iso_c_binding, only: c_intptr_t, c_ptrdiff_t, c_ptr, c_loc, c_f_pointer, c_sizeof
  implicit none

  integer, target :: a(2)
  type(c_ptr) :: p, p1, p2
  integer(c_intptr_t) :: p1i, p2i, pi
  integer(c_ptrdiff_t) :: d
  integer, pointer :: ip

  a(1) = 6
  a(2) = 7

  p1 = c_loc(a(1))
  call c_f_pointer(p1, ip)
  print *, ip

  p1i = transfer(p1, p1i)
  print *, p1i

  p2 = c_loc(a(2))
  call c_f_pointer(p2, ip)
  print *, ip

  p2i = transfer(p2, p2i)
  print *, p2i

  d = p2i - p1i
  print *, d
  print *, c_sizeof(a(1))

  pi = p1i + d
  print *, pi

  p = transfer(pi, p)
  call c_f_pointer(p, ip)
  print*, ip
end program
#include <stdint.h>
#include <stddef.h>
#include <stdio.h>

int main() {
  int a[2];
  void * p, * p1, * p2;
  intptr_t p1i, p2i, pi;
  ptrdiff_t d;
  int * ip;

  a[1] = 6;
  a[2] = 7;

  p1 = &a[1];
  ip = p1;
  printf("%i\n", *ip);

  p1i = (intptr_t)p1;
  printf("%i\n", p1i);

  p2 = &a[2];
  ip = p2;
  printf("%i\n", *ip);

  p2i = (intptr_t)p2;
  printf("%i\n", p2i);

  d = p2i - p1i; // Could have been (char*)p2 - (char*)p1;
  printf("%i\n", d);
  printf("%i\n", sizeof(a[1]));

  pi = p1i + d; // Could have been (intptr_t)((char*)p1 + d);
  printf("%i\n", pi);

  p = (void*)pi;
  ip = p;
  printf("%i\n", *ip);
}

Would anybody with a bit more experience on the C side of things be able to confirm or deny my thinking here?

Nice example! The C11 standard says:

The following type designates a signed integer type with the property that any valid
pointer to void can be converted to this type, then converted back to pointer to void,
and the result will compare equal to the original pointer:

    intptr_t

So I think yeah, what you’re doing with transfer is not only legal, but it’s the exact definition of the relationship between type(c_ptr) or void* and integer(c_intptr_t).

The statement also says that’s a signed integer, which may be important for the pointer arithmetics.

That was exactly what I saw that lead me down this path. However, I did have a discussion with someone that suggested that

any valid pointer to void can be converted to this type, then converted back to pointer to void,
and the result will compare equal to the original pointer

does not strictly mean

intptr_t ip;
void* p;
sizeof(ip) == sizeof(p);

So, for safety sake, one should probably do something like the following to get a compiler error if things don’t line up.

integer(c_intptr_t) :: unused_i
type(c_ptr) :: unused_p
integer, parameter :: pointer_sized = &
    merge(c_intptr_t, -1, storage_size(unused_i) == storage_size(unused_p))
integer(pointer_sized) :: ip
1 Like