%re and %im in constants

The program below works well with gfortran but ifx, lfortran and AMD flang object to it in 3 different ways. Is it standard-comforming? It’s not clear to me whether %re and %im are allowed when defining a constant.

  implicit none ! file re_imconsts.f90 see lfortran issue #7298 
  integer,parameter:: dp = kind(1d0)
  COMPLEX(dp),PARAMETER :: x = (1D0,2D0)/3d0
  REAL(dp),PARAMETER :: re = x%re
  REAL(dp),PARAMETER :: ri = x%im
  print "(2F18.15)",re,ri
end program

Lfortran complains about ri but not re. AMD flang complains about re but not ri, and ifx complains about both.

1 Like

The difference you see is likely that the default behavior after encountering an error is different. If you comment out the one getting the error I would be surprised if you then did not get an error on the one not initially complained about. Many compilers have options on how many errors to report before exiting, and the default varies.

I think it should work. What happens if you use REAL() and AIMAG() instead, out of curiosity. As I read it %re and %im create a variable that can appear on the LHS of an assignment, be passed and returned to procedures, and be treated as a variable, where in contrast REAL() and AIMAG() are procedure calls that return a temporary value.

@urbanjost raises some important matters but they don’t answer my question. I was defining a constant, not a variable, and %re and %im were on the RHS not the LHS of an assignment. Lfortran is my only compiler which stops looking for more errors by default after finding one.
When I used REAL and AIMAG all those compilers and also g95 were happy with the program except ifx, which said “Fortran 2018 specifies that an elemental intrinsic function here be of type integer or character and each argument must be an initialization expr of type integer or character.
REAL(dp) ,PARAMETER :: ri = aimag(x)”
But that restriction to integer or character does not exist in F2018. The last standard requiring it was F95.

My intention was to say it should work according to the most recent standard. Mentioning it can be used on the LHS and used to return a value from a subroutine call was just emphasizing you should be able to use it anywhere a variable can be used.

What version of ifx are you using?

FYI, I also tried using a KIND inquiry (9.4.5) and while gfortran accepted it, ifx didn’t:
integer, parameter :: k = x%kind

Yes, but it is silly (in the technical sense), as you found out. Real(x) and Aimag(x) would have worked just as well and stand a better chance of being correctly implemented.

I think your code should work, but there are, of course, some obvious workarounds for this if it doesn’t. Here is one

program reim
   implicit none
   integer,parameter:: dp = kind(1d0)
   REAL(dp),PARAMETER :: re = 1.0_dp / 3.0_dp
   REAL(dp),PARAMETER :: ri = 2.0_dp / 3.0_dp
   !COMPLEX(dp),PARAMETER :: x = cmplx(re,ri,kind=dp)
   COMPLEX(dp),PARAMETER :: x = (re,ri)
   print "(2F18.15)", x, re, ri
end program reim

$ gfortran -std=f2018 reim.f90 && a.out
 0.333333333333333 0.666666666666667
 0.333333333333333 0.666666666666667

This surprised me a little because it accepts (re,ri) as a constant. I thought that one had to use the intrinsic cmplx() for parameters and variables (as in the commented line), and that the parentheses notation only worked for literal constants. Am I remembering this restriction incorrectly, or is that now standard?

Perhaps worth contributing this as an example to GitHub - klausler/fortran-wringer-tests: A collection of non-portable Fortran usage, standard-conformant or otherwise. There are some related exampled named complex-*.f90

As written here,

  • The %RE and %IM syntax references components of complex variables. Some compilers just treat them as if they were expressions equivalent to REAL() and AIMAG() intrinsic function references. The distinction matters when %RE and %IM references are associated with REAL dummy arguments. Exactly one compiler correctly implements a pointer initialization target that applies %RE or %IM to an array slice.

Indirectly heard flang works as well. Would be nice if someone can confirm. When I get a chance I might try with Godbolt

man-pages

https://urbanjost.github.io/M_intrinsics/cmplx.3fortran.html

https://urbanjost.github.io/M_intrinsics/aimag.3fortran.html

https://urbanjost.github.io/M_intrinsics/real.3fortran.html

(named-constant, named-constant) form for complex-literal-constant was an F2003 innovation.

1 Like

That is consistent with gfortran -std=f95 reim.f90, which fails to compile and prints an appropriate error message.

My ifx --version command says

ifx (IFX) 2025.1.0 20250317

Its error message mentioned Fortran 2018 presumably because I had not specified the -standoption. I intend to raise the matter with the Intel Fortran forum.
There seem to be at least two different compilers called flang. My one’s
--version is


AMD clang version 17.0.6 (CLANG: AOCC_5.0.0-Build#1377 2024_09_24)
Target: x86_64-unknown-linux-gnu
Thread model: posix
InstalledDir: /home/john/AMD/aocc-compiler-5.0.0/bin

It was happy with the REAL and AIMAG variants of my program.

  implicit none ! file re_imconsts.f91 see lfortran issue #7298
  integer,parameter:: dp = kind(1d0)
  COMPLEX(dp),PARAMETER :: x = (1D0,2D0)/3d0
  REAL(dp),PARAMETER :: re = x%re
  REAL(dp),PARAMETER :: ri = x%im
  print "(2F18.15)",re,ri
end program
$ flang-new complex-designator.f90 && ./a.out 
 0.333333333333333 0.666666666666667

$ flang-new -v
Debian flang-new version 19.1.7 (3)
Target: x86_64-pc-linux-gnu
Thread model: posix
InstalledDir: /usr/lib/llvm-19/bin
Found candidate GCC installation: /usr/lib/gcc/x86_64-linux-gnu/13
Found candidate GCC installation: /usr/lib/gcc/x86_64-linux-gnu/14
Selected GCC installation: /usr/lib/gcc/x86_64-linux-gnu/14
Candidate multilib: .;@m64
Candidate multilib: 32;@m32
Candidate multilib: x32;@mx32
Selected multilib: .;@m64

1 Like

A very ugly set of tests of some complex value features might be useful as a starting point for anyone that wants to make a test program … gfortran 15 passes it, and it hits some dusty corners. Not sure how obvious some of the answers should be, so it definitely needs more assert-like tests and beautified, etc.

complex value tests
program testit
use, intrinsic :: iso_fortran_env, only : real32, real64, real128
implicit none
character(len=*),parameter :: it='(*(1x,g0))'
character(len=*),parameter :: break='(/,80("-"),t4,a)'
integer,parameter          :: dp = kind(1.0d0)
complex(dp),parameter      :: x = (1d0,2d0)/3d0
real(dp),parameter         :: re = x%re
real(dp),parameter         :: ri = x%im
complex                    :: z4
complex                    :: zr = (1.0, 2.0)
complex                    :: zthree(3)
complex(kind=dp)           :: z8
complex(kind=dp)           :: zd=cmplx(4.0e0_dp,5.0e0_dp,kind=dp)
doubleprecision            :: xd=huge(0.0d0)
integer                    :: i
real(kind=dp)              :: precise =1.2345678901234567d0
   ! basic
   z4%re = -3  ! ze%im will not be properly defined
   print *,z4
   z4 = cmplx(-3) ! ok even with an integer value, result of cmplx with no kind always default complex kind
   print *,z4
   ! treat a complex as two real values when using a format
   print '(1x,g0,1x,g0,1x,g0)','z4=',z4
   ! components defined as components of a complex value
   print "(2f18.15)",re,ri
   z4 = cmplx(1.e0, 2.e0)
   z8 = cmplx(3.e0_real64, 4.e0_real64,kind=real64)
   print it,  'value=',z4
   print it, 'imaginary part=',aimag(z4),'or', z4%im
   print it, 'kinds other than the default may be supported'
   print it,  'value=',z8
   print it, 'imaginary part=',aimag(z8),'or', z8%im

   print break, 'an elemental function can be passed an array'
   zthree=[z4,z4/2.0,z4+z4]
   print it, 'given a complex array:'
   print it,  (zthree(i),new_line('a'),i=1,size(zthree))
   print it, 'the imaginary component is:'
   print it, aimag( zthree )

   print break, ' working with higher precision values'
   ! using kind=dp makes it keep doubleprecision precision
   ! otherwise the result would be of default kind
   z8 = cmplx(precise, -precise )
   print *, 'lost precision z8=',z8
   z8 = cmplx(precise, -precise ,kind=dp)
   print *, 'kept precision z8=',z8

   print break, 'assignment of constant values does not require cmplx(3)'
   ! the following is intuitive and works without calling cmplx(3)
   ! but does not work for variables just constants
   z8 = (1.1111111111111111d0, 2.2222222222222222d0 )

   print *, 'z8 defined with constants=',z8

   print break, 'what happens when you assign a complex to a real?'
   precise=z8
   print *, 'lhs=',precise,'rhs=',z8
   ! descriptors are an alternative
   print *, real(zr), aimag(zr)
   print *, dble(zd), aimag(zd)
   write(*,*)xd,real(xd,kind=kind(0.0d0)),dble(xd)
  
   print break, ' elemental '
   zthree=cmplx([10,20,30],-1)
   print *, all(zthree .eq. [(10,-1),(20,-1),(30,-1)] ),'zthree=',zthree

   zthree(1:2)%re=[100,200]
   print *, all(zthree.eq.[(100,-1),(200,-1),(30,-1)]),'Array subsection on LHS zthree=',zthree

   print break, ' subroutine parameter '
   ! should be able to get changed return value and use %re and %im on LHS

   z8=(3,4)
   call doubleup(z8%re)
   call doubleup(z8%im)
   write(*,*)z8==(6,8),'subroutine z8=',z8

   print break, ' LHS and passed to function '
   z8=(5,-4)
   z8%re=du(z8%re)
   z8%im=du(z8%im)
   write(*,*)z8==(10,-8),'function and LHS z8=',z8

contains 

subroutine doubleup(x)
real(kind=dp),intent(inout) :: x
   x=2*x
end subroutine doubleup

function du(x) result(answer)
real(kind=dp),intent(in) :: x
real(kind=dp)            :: answer
   answer=2*x
end function du

end program testit

Good test program @urbanjost much more comprehensive than mine. My only compiler that passed yours was gfortran, but it would be good to know what NAG does with it as it’s usually very good on standard-conformance. I think your program was good F2018 but the format '(*(1x,g0))' was not in F2008.

> nagfor testit.f90
NAG Fortran Compiler Release 7.2(Shin-Urayasu) Build 7203
Warning: testit.f90, line 99: REAL128 explicitly imported into TESTIT but not used
Warning: testit.f90, line 99: REAL32 explicitly imported into TESTIT but not used
Questionable: testit.f90, line 45: Intrinsic function CMPLX with double precision argument and no KIND= argument returns single precision result
[NAG Fortran Compiler normal termination, 3 warnings]
> nagfor -f2008 testit.f90
NAG Fortran Compiler Release 7.2(Shin-Urayasu) Build 7203
Warning: testit.f90, line 99: REAL128 explicitly imported into TESTIT but not used
Warning: testit.f90, line 99: REAL32 explicitly imported into TESTIT but not used
Questionable: testit.f90, line 45: Intrinsic function CMPLX with double precision argument and no KIND= argument returns single precision result
[NAG Fortran Compiler normal termination, 3 warnings]
1 Like