Implicit real - complex conversion in fortran

New standards of fortran are more strict about the mismatches between the calls and the procedure definition. However, there are a lot of legacy codes where, for instance, complex array is viewed as a collection of reals. This still can be properly compiled by lowering such errors to warnings. In gfortran it is achieved with the -fallow-argument-mismatch . This provides a temporary working solution, but is unsatisfactory in long-run.

program polymorphic_types_wrk
  use Maux_wrk
  implicit none
  integer, parameter       :: dp = kind(1.d0), dim = 10
  real(dp)                 :: wd(2 * dim)
  complex(dp)              :: wz(dim)

  call random_number(wd)
  call copy_real_complex_nonconformant(dim, wd, wz)
  
end program polymorphic_types_wrk

module Maux_wrk

contains
    subroutine copy_real_complex_nonconformant(dim, wd, wz)
    implicit none
    integer, parameter :: dp = kind(1.d0)
    integer, intent(in)     :: dim
    real(dp), intent(in)    :: wd(*)
    complex(dp), intent(out):: wz(*)

    call zcopy(dim, wd, 1, wz, 1)

  end subroutine copy_real_complex_nonconformant
  
end module Maux_wrk

In this example, zcopy is a standard BLAS subroutine. The goal is to copy an array of reals to an array of complexes assuming the data is contiguous.

What would be your recommendation of implementing this code without the use of -fallow-argument-mismatch ? I would like to be more standard conforming, and I would not like to disable arguments check everywhere.

1 Like

One possible trick is go over c_loc() and c_f_pointer() to create a complex pointer to a real array. The following code should to the trick:

program test
  use iso_c_binding, only : c_loc, c_f_pointer
  implicit none

  integer, parameter :: nn = 5
  real, target :: rarray(2 * nn)
  complex :: carray(nn)
  complex, pointer, contiguous :: cptr(:)
  integer :: ii

  rarray(:) = [(real(ii), ii = 1, 2 * nn)]
  call c_f_pointer(c_loc(rarray), cptr, [nn])
  
  carray(:) = 0.0
  write(*, "(a)") "Content of carray before copy:"
  write(*, "(2F6.1)") carray

  call ccopy(cptr, carray)

  write(*, "(a)") "Content of carray after copy:"
  write(*, "(2F6.1)") carray

  carray(:) = 0.0
  write(*, "(a)") "Content of carray before copy (F77):"
  write(*, "(2F6.1)") carray

  call ccopy_f77(nn, cptr, carray)

  write(*, "(a)") "Content of carray after copy (F77):"
  write(*, "(2F6.1)") carray

contains

  subroutine ccopy(carray1, carray2)
    complex, intent(in) :: carray1(:)
    complex, intent(out) :: carray2(:)

    carray2(:) = carray1

  end subroutine ccopy


  subroutine ccopy_f77(nn, carray1, carray2)
    integer, intent(in) :: nn
    complex, intent(in) :: carray1(*)
    complex, intent(out) :: carray2(*)

    integer :: ii

    do ii = 1, nn
      carray2(ii) = carray1(ii)
    end do

  end subroutine ccopy_f77
    
end program test

I think this should be standard conforming and robust, without the need for degradation of the argument mismatch detection. The target attribute is needed on the real array, and the contiguous attribute of the complex pointer should ensure, that no copy-in/copy-out happens, when passing it to F77-style routines.

1 Like

You can also use transfer:

wz = transfer(wd, wz)
2 Likes

Or if you prefer:

wz%re = wd(1::2)
wz%im = wd(2::2)

Indeed. If it just a copy, transfer() is a much simpler solution. If the problem is more general (passing real arrays to complex routines), the c_loc() solution would help to avoid to create unnecessary copies…

You mean wz(1:dim) = transfer(wd(1:2*dim), z) ?

Definitely, but one should check they are contiguous.

By the way it is so common to see a complex array like a real array that I suggest a small language enhancement, basically allowing a real pointer to point to a complex array on the provision that the real pointer has an additional first dimension (that will be of size 2 after the array assignment):

complex, target :: a(N,M,K)
real, pointer :: ap(:,:,:,:)
ap => a
print *,shape(a) 

will print (whatever are N, M, K):

  2, N, M, K

The converse may not be always possible.
That previous example, with this syntax enhancement, will be:

real, pointer :: wd(:,:)
complex, target :: wz(dim) 

wd => wz
call random_number(wd)
...

Just an half idea thrown without thinking too much.
Cheers

I would point out this thread,

and the proposal that @PierU has prepared: Adding a proposal to allow complex pointers to real arrays and vice-versa by PierUgit · Pull Request #325 · j3-fortran/fortran_proposals · GitHub

No, I meant what I had written.

I don’t need to put the size of the array on the left side or the right side as I know that they are of the correct size. Moreover I used as mold the same array on the left.
That was handy as, this way, I don’t need to specify the size in the transfer function. The output will be a one dimension array able to contain all the meaningful data present in the source.

But I knew that in this case everything will work. TRANSFER (The GNU Fortran Compiler)

If the left array has more then one dimension one have to call also the reshape function.

How can I uptick (or endorse) your proposal?

I had no hand in the proposal. The best support would probably be to read the proposal, provide feedback, give it a like on GitHub and voice your support in a comment.

You could even submit a symbolical letter like this one:

(Source: finally. #embed | The Pasture)

It has been discused a couple of times, but it is not (standard conforming)

Why is it not standard conforming? (I’ve probably missed those discussions, you can also just direct me to them.) The real type is interoperable with float, so c_loc() gives a C-pointer to the array data. In C, there should be no difference between a float array and a float _Complex array half of its size. So, in C, I could create a float _Complex pointer to this data and access it as if they were complex numbers. But since float _Complex is interoperable with complex in Fortran, I can use c_f_pointer to create a complex pointer to it. I don’t see any problems here.

My “Modern Fortran” contains the following about c_f_pointer (cptr, fptr [, shape]): cptr must not be the C address of a Fortran variable that does not have the ŧarget attribute. But in my example, the real array has the target attribute, so I see no problem here either.

But I might, of course, miss something obvious, so any clarification would be welcome.

In c_f_pointer(c_loc(x),y,...), the standard requires x and y to be of the same type and kind.

@PierU Thanks a lot! In the mean time, I have also found the relevant part in the standard, and I still think,that my example is standard conforming.

Case (ii) does not apply, because the c_loc argument (a real array) is interoperable.

Case (i) only requires, that FPTR shall be of type and type parameter, which are interoperable with the data entity CPTR points to. And since ̇CPTR points to the beginning of a contiguous memory block containing an even number of real numbers, it is IMO interoperable with the complex data type. So the requirement is fulfilled.

And finally the additional requirement for CPTR

The value of CPTR shall not be the C address of a Fortran variable that does not have the TARGET
attribute.

is also fulfilled. Do I miss something? Can you think about any realistic scenario, where this workaround would fail with a standard conforming compiler?

Of course, it would be nice to have better ways to do it (like your proposal), but this way is probably a possible (IMO standard conforming :wink:) workaround so far.

You have changed some words, which probably also changes the interpretation :wink:

You’re right, I was quoting somewhat sloppy. So the exact wording is

If the value of CPTR is the C address of an interoperable data entity, FPTR
shall be a data pointer with type and type parameter values interoperable with
the type of the entity

I am definitely not a language lawyer: But, if CPTR is the C-address of a contiguous block of an even number or real/float numbers, then it points to a data entity, which is interoperable with complex, doesn’t it?

The only scenario I can imagine, where this would fail (and not being standard conforming), if the representation of the data in a complex number was not equivalent to the representation of the data in a real array with two elements. And if I understood the discussion correctly, it is not likely to ever happen.

The standard has not changed at all in this regard. The first Fortran standard, FORTRAN 66, says:

The actual arguments, which constitute the argument list, must agree in order, number and type with the corresponding dummy arguments in the defining program unit.

The current standard says, “The dummy argument shall be type compatible with the actual argument.” However, COMPLEX is not type compatible with REAL.

Compilers have gotten better at diagnosing argument type mismatches, and some do it by default, which is good.

1 Like

interoperable has a stricter meaning than just pointing to a right memory area, it ties together a specific Fortran type to a specific C type.

No doubt the c_f_pointer trick will work with virtually all the existing compilers (and as a matter of fact I do use it), because they all follow the implicit convention where a complex number is represented in memory by the sequence real part / imaginary part. Nonetheless, it doesn’t make it standard conforming. It’s the same as passing a complex array actual argument to a dummy real array argument of a routine without explicit interface: it “works” (for the same reason as above), but it’s not standard conforming.

1 Like

The current standard says, “The dummy argument shall be type compatible with the actual argument.” However, COMPLEX is not type compatible with REAL.

What is the impediment to this? If the standards committee were to make them officially compatible would that break something else in the standard?