- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I have the following code snippet:
PROGRAM main
USE ISO_C_BINDING
USE ISO_FORTRAN_ENV
IMPLICIT NONE (type, external)
! COMPLEX(C_FLOAT_COMPLEX), ALLOCATABLE, TARGET :: a(:)
! COMPLEX(real32), ALLOCATABLE, TARGET :: a(:)
COMPLEX, ALLOCATABLE, TARGET :: a(:)
TYPE(C_PTR) :: re_ptr, im_ptr, ptr
ALLOCATE(a(10))
ptr = C_LOC(a)
re_ptr = C_LOC(a(1)%re)
im_ptr = C_LOC(a(1)%im)
CALL sub(ptr, re_ptr, im_ptr)
WRITE(*, *) "Finished!"
CONTAINS
SUBROUTINE sub(ptr, re_ptr, im_ptr) BIND(C)
TYPE(C_PTR), VALUE :: ptr, re_ptr, im_ptr
WRITE(*, *) "CALL sub"
END SUBROUTINE sub
END PROGRAM main
This works in gfortran >= 9, and did also work in ifort <= 2021.5.0 and ifx <= 2022.0.0. It also works in 'flang-new'.
In ifort >= 2021.6 and ifx >= 2022.1 this example no longer compiles.
In the most recent ifx (2024.1) the compiler gives the message:
example.F90(13): error #9022: The argument to C_LOC must be a variable with the POINTER or TARGET attribute. [REAL]
re_ptr = C_LOC(a(1)%re)
^
example.F90(14): error #9022: The argument to C_LOC must be a variable with the POINTER or TARGET attribute. [AIMAG]
im_ptr = C_LOC(a(1)%im)
^
compilation aborted for example.F90 (code 1)
You can try the example in the compiler explorer yourself.
I tried to experiment with the kind of the COMPLEX, and for instance set it the c_float_complex to make sure it is interoperable with the float _Complex in C, bit that did not change anything.
I am not sure what the Fortran standard says about the C_LOC of the real or imaginary parts of a complex variable, so there is of course the possibility that what I try to do is illegal...
However, I do suspect this might be a bug in ifx.
Any comments?
Thanks in advance.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Gentlemen, look for the fix for this issue in the 2024.2 release that is planned to be available in mid-2024.
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I think this should work, but am held back because NAG Fortran doesn't like it either. The issue is whether a complex-part-designator of a variable with TARGET also has TARGET. The standard says that subobjects of a variable with TARGET do have TARGET. It also says that the real and imaginary parts of COMPLEX variables are subobjects.
I need to make some inquiries.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Malcolm Cohen (NAG, and standard editor) agrees with me that this is a bug. Here is a smaller reproducer:
use, intrinsic :: iso_c_binding
complex, target :: a = (1.,2.)
type(C_PTR) :: p
p = C_LOC(a%re)
end
My reading of the standard is that a complex-part-designator of a variable is a variable (9.2 and 9.1), that the real and imaginary parts of a complex value are "subobjects" (19.6.1), and that all nonpointer subobjects of a variable that has the TARGET attribute also have the TARGET attribute (8.5.18).
@Barbara_P_Intel , please submit this to the developers. Thanks.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Here's a test that illustrates both the above bug and a related one.
use, intrinsic :: iso_c_binding
complex, target :: a = (1.,2.)
type(C_PTR) :: cp
real, pointer :: p
cp = C_LOC(a%re)
call C_F_POINTER (cp, p)
if (p /= 1.0) then
print *, "C_LOC test failed"
else
print *, "C_LOC test passed"
end if
call sub (a%im, 2.0)
contains
subroutine sub (r,x)
real, pointer, intent(in) :: r
real, intent(in) :: x
if (r /= x) then
print *, "Ptr argument test failed"
else
print *, "Ptr argument test passed"
end if
return
end
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
@hakostra1, thank you for reporting this C_LOC issue and for showing that it's a regression. That takes some work!
@Steve_Lionel, thank you for the research and the second faulty error message.
I filed a bug report, CMPLRLLVM-57418. We'll let you know when it's fixed
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thanks to both of you!
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Gentlemen, look for the fix for this issue in the 2024.2 release that is planned to be available in mid-2024.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Awesome, thank you so much!
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I can confirm that the newly released 2024.2 contains the fix, thank you so much!

- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page