Real view on complex array using c_pointer

@oyvind ,

The use of an error code is entirely up to you and based on your (and your team’s) adopted programming practice(s). You can also consider INTENT(OUT) for the second dummy argument toward the real pointer that can just clear up the usage.

Putting that aside, my suggestion will be to strive for as much compilation time diagnostics as possible which you can get here by using the CONTINUOUS attribute.

   subroutine real_view(cp, rp)
      use ISO_C_binding, only: c_f_pointer, c_loc
      complex(wp), contiguous, pointer, intent(in) :: cp(:)
      real(wp), intent(out), pointer :: rp(:)
      
      if ( associated(cp) ) then
         call c_f_pointer(c_loc(cp), rp, shape=[2*size(cp)])
      end if

   end subroutine real_view

Now consider the following:

   subroutine sub( pc )
      complex(wp), pointer :: pc(:)
      real(wp), pointer :: r(:)
      ! Elided is the explicit interface
      call real_view( pc, r )   
   end subroutine 

C:\Temp>gfortran -c c.f90
c.f90:19:22:

19 | call real_view( pc, r )
| 1
Error: Actual argument to contiguous pointer dummy ‘cp’ at (1) must be simply contiguous

Also, you do not need a temporary pointer object on the caller side, the Fortran standard now permits automatic targetting so you can do

   complex(wp), target, allocatable :: c(:)
   real(wp), pointer :: rp(:) => null() !<-- Be mindful of this initialization!
   
   ! Create complex 2-element array
   allocate(c(2))
   c(1) = cmplx(1_wp, 2_wp, wp)
   c(2) = cmplx(3_wp, 4_wp, wp)

   ! Create a 4-element real "view" into the same memory area
   call real_view(c, rp)

By the way, be mindful the initialization of the real pointer in the declaration real(wp), pointer :: rp(:) => null() will impart the SAVE attribute to that rp object, something you may not want!

2 Likes