Real view on complex array using c_pointer

@oyvind , see the comments by @certik here and here.

Unless you are completely enamored with object-oriented programming (OOP) approach, a somewhat better option will be to follow object-based model as suggested above. Note there is never complete safety but with object-based you can gain some simplicity here: you can hone in on a single data allocation and avoid data duplication and in addition, a lot of the OOP data (and state) management code can be avoided.

Here’s a simple illustration, you can try it with the free Intel oneAPI IFORT compiler.

With this, you can get most of the safety in working with pointers.

module c_m
   use, intrinsic :: iso_c_binding, only : c_loc, c_f_pointer
   private
   type, public :: c_t
      private
      complex, allocatable :: m_c(:)
      complex, pointer :: m_cview(:) => null()
      real, pointer :: m_rview(:) => null()
   end type
   public :: init_c, rview, cview 
contains
   subroutine init_c( this, size_c )
      type(c_t), intent(inout), target :: this
      integer, intent(in)              :: size_c
      ! Elided are checks toward initialization and allocation status, etc.
      allocate( this%m_c(size_c) )
      this%m_cview => this%m_c 
      call c_f_pointer( c_loc(this%m_c), this%m_rview, shape=[ 2*size_c ] )
      this%m_rview = 0.0
   end subroutine 
   function rview( this ) result(r)
      type(c_t), intent(in), pointer :: this
      real, pointer :: r(:)
      r => this%m_rview
   end function 
   function cview( this ) result(c)
      type(c_t), intent(in), pointer :: this
      complex, pointer :: c(:)
      c => this%m_cview
   end function 
end module 
   use c_m
   type(c_t), target :: foo
   integer, parameter :: rsize=4
   call init_c( foo, size_c=rsize/2 )
   rview( foo ) = [( real(i), integer :: i = 1, rsize )]  !<-- Fortran 2008 feature, inadequately supported by gfortran
   print *, "cview() = ", cview( foo ) 
   print *, "rview() = ", rview( foo ) 
end

C:\Temp>ifort /standard-semantics c.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.2.0 Build 20210228_000000
Copyright (C) 1985-2021 Intel Corporation. All rights reserved.

Microsoft (R) Incremental Linker Version 14.28.29337.0
Copyright (C) Microsoft Corporation. All rights reserved.

-out:c.exe
-subsystem:console
c.obj

C:\Temp>c.exe
cview() = (1.000000,2.000000) (3.000000,4.000000)
rview() = 1.000000 2.000000 3.000000 4.000000

C:\Temp>

2 Likes