Inversion of complex numbers with a zero imaginary part

I was taking the log of a complex number, \log(-1/z). The imaginary part of z is 0 and the real part is positive. Let’s say z = (1.0, 0.0). The logarithm evaluates to two different numbers (\pm i\pi) depending on whether the imaginary part of -1/z is 0.0 or -0.0, as explained in the docs. In this case, 1/z evaluates to (1.0,0.0), which means that -1/z is (-1.0,-0.0).

Given that 1/(1.0,-0.0) evaluates to (1.0, 0.0), I was expecting that 1/(1.0, 0.0) evaluate to (1.0, -0.0). The numbers 0.0 and -0.0 are equal, but they are not equivalent (on my processor), as seen by the different branch choices for their logarithms triggered by \pm0.0i and of course by the different outputs of ieee_is_negative(0.0) and ieee_is_negative(-0.0).

This leads directly to the two seemingly conflicting relations

\log(-z) \ne -log(-1/z) \\ \log(-z^*) = -log(-1/z^*)

as seen in the following test example.

program test
  use, intrinsic :: iso_fortran_env, only: real64

  implicit none

  complex(real64) :: z = 5.0_real64
  complex(real64) :: wz, wzstar

  wz     = 1/z
  wzstar = conjg(wz)

  print*, "z:  ",            z
  print*, "1/z: wz = ",      wz
  print*, "1/z*: wzstar = ", wzstar

  ! -- logarithm comparisons
  print*, "log(-wz) = -log(-1/wz) ? ::",     log(-wz) .eq. -log(-1/wz)
  print*, "log(-wzstar) = -log(-1/wzstar) ? ::", log(-wzstar) .eq. -log(-1/wzstar)

end program test
---
Output
 z:                 (1.0000000000000000,0.0000000000000000)
 1/z: wz =                (1.0000000000000000,0.0000000000000000)
 1/z*: wzstar =               (1.0000000000000000,-0.0000000000000000)
 wz .eq. 1/z :: T
 wz .eq. wzstar  :: T
 log(-wz) = -log(-1/wz) ? :: F
 log(-wzstar) = -log(-1/wzstar) ? :: T

The last equality test is True because the imaginary part of wzstar is -0.0, which becomes 0.0 when wzstar gets inverted, but the one before it is False because the imaginary part of wz is 0.0 and does not become -0.0 when inverted.

Why does 1/z not acquire a negative sign on its imaginary part ? Could this be compiler (GCC v. 14.2.1) specific? Maybe this was an intentional decision made some time ago — maybe it’s quite subtle. Any insight is greatly appreciated.

1 Like

You may want to check this article - On Quality of Implementation of Fortran 2008 Complex Intrinsic Functions on Branch Cuts, byt Anton Shterenlikht, On Quality of Implementation of Fortran 2008 Complex Intrinsic Functions on Branch Cuts | ACM Transactions on Mathematical Software.
There is a large variation in the quality of such calculations and this would seem to be part of that.

1 Like

I am not certain what is the correct behavior in these cases, but I do know from past experience that the negative zero results depend on how the expression is written. For example, -z might not be the same as (-1.0)*z, or a*z, might not the the same when a==-1.0 and is evaluated at run time rather than at compile time. Consider the following small program.

program ieee
   use ieee_arithmetic
   implicit none
   complex :: z

   z = (1.0,0.0)
   call writeit(z)

   call writeit(-z)
   call writeit( -1.0*z )
   call writeit( (-1.0)*z )

   call writeit( -1.0/z )
   call writeit( (-1.0)/z )
   
contains
   subroutine writeit(z)
      complex, intent(in) :: z
      write(*,*) z, ieee_is_negative(z%re), ieee_is_negative(z%im)
      return
   end subroutine writeit
end program ieee

$ gfortran ieee.f90 && a.out
             (1.00000000,0.00000000) F F
           (-1.00000000,-0.00000000) T T
           (-1.00000000,-0.00000000) T T
            (-1.00000000,0.00000000) T F
           (-1.00000000,-0.00000000) T T
            (-1.00000000,0.00000000) T F

Note that both the multiplication and the division expressions show the same behavior.