Real and imaginary parts of complex number

What’s the most modern way to extract the real/imaginary parts of a complex number in Fortran? I’m aware of real and aimag, and %re/%im - what’s the most preferred method?

2 Likes

Indeed, with compilers conformant with Fortran 2008 and later revisions, %RE and %IM is the way to go in my “book” too. Note, however, it is processor-dependent whether one gets direct reference to the data, or the address of a copy of it when it comes to the more common scenarios with complex numbers and which is arrays of them.

module m
   use, intrinsic :: iso_c_binding, only : c_loc, c_size_t
   character(len=*), parameter :: fmtz = "(g0,1x,z0)"
   integer(c_size_t), parameter :: mold = 0
contains
   impure elemental function cmag( x, y ) result(r)
      real, intent(in), target :: x, y
      real :: r
      print fmtz, "mag: address of x (hex): ", transfer( c_loc(x), mold=mold )
      r = sqrt(x**2 + y**2)
   end function
end
   use m
   complex, target :: z(3)
   real :: q( size(z) )
   z%re = [ 1.0, 2.0, 3.0 ]
   z%im = 0.0
   print fmtz, "main: address of z(1)%re (hex): ", transfer( c_loc(z(1)%re), mold=mold )
   print fmtz, "main: address of z(2)%re (hex): ", transfer( c_loc(z(2)%re), mold=mold )
   print fmtz, "main: address of z(3)%re (hex): ", transfer( c_loc(z(3)%re), mold=mold )
   q = cmag( z%re, z%im )
   print *, q
end

C:\Temp>ifort /standard-semantics i.f90 -o i.exe
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:i.exe
-subsystem:console
i.obj

C:\Temp>i.exe
main: address of z(1)%re (hex): 72478FFAE8
main: address of z(2)%re (hex): 72478FFAEC
main: address of z(3)%re (hex): 72478FFAF0
mag: address of x (hex): 72478FFAF4
mag: address of x (hex): 72478FFAF4
mag: address of x (hex): 72478FFAF4
1.000000 2.000000 3.000000

C:\Temp>gfortran i.f90 -o gcc-i.exe

C:\Temp>gcc-i.exe
main: address of z(1)%re (hex): 87FDB0
main: address of z(2)%re (hex): 87FDB8
main: address of z(3)%re (hex): 87FDC0
mag: address of x (hex): 87FDB0
mag: address of x (hex): 87FDB8
mag: address of x (hex): 87FDC0
1.00000000 2.00000000 3.00000000

C:\Temp>

3 Likes

Thanks to you both. I noticed that you can’t do the following, though: (a+b)%re which is unfortunate. At least, gfortran calls that an unclassifiable statement.

1 Like

Fortran allows the somewhat more verbose ASSOCIATE block with type-inference:

      associate ( t => a + b )
         ! consume t%re as read-only here
      end associate
4 Likes

If you want to convert the real or imaginary part of the complex data entity to a different KIND, I would use REAL or AIMAG. Otherwise, %re and %im are the new, shiny approach.

Equally unfortunate, perhaps, is that one cannot expect

("abc" // "def")(3:4)

to yield “cd”. Users moving to a compiled language such as Fortran after extensive usage of interpreted languages will probably encounter and comment on such restrictions in the beginning.

2 Likes

Or:

(A+B+sin(C))(5:10)

where A, B and C are arrays. I will admit that it is not super readable, compared to Python’s (A+B+sin(C))[5:10], was readability the reason it is not allowed?

Indeed. if the function is not elemental, then it would have to compute 1 million elements only to throw away most of them to get (5:10) out. This is exactly how Python would do it also. So it can be wasteful, and that’s probably the reason it is not allowed.

I think there is a bug in gfortran when using %re and %im of complex type components. Consider the following minimal program:

program main
    use, intrinsic :: iso_fortran_env, only: dp => real64
    implicit none

    type complex_wrap
        complex(dp), dimension(:), allocatable :: z
    end type

    type(complex_wrap) :: w

    allocate(w%z(2))
    w%z(1) = (1, 2)
    w%z(2) = (3, 4)

    print*,w%z%re
    call print_arr(w%z%re)

contains

    subroutine print_arr(x)
        real(dp), intent(in), dimension(:) :: x
        print*,x
    end subroutine

end program main

The print statement in the main program prints “1 , 3” whereas when printing from the subroutine the result is “1, 2”. ifort compiles the program without warnings and prints “1, 3” in both cases.

I’ve submitted a bug report:
Bug 102891

4 Likes

I can confirm the bug with GFortran 11.0.1 20210403 (experimental) on Apple M1 installed using Conda.