- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I have a frustrating problem. I have a routine that write out some (MPI) distributed data in an orderly and coordinated manner. In that process of ordering and writing out the data I need to do some MPI-calls, which should be trivial.
The data I write out are both real's and integer's and even derived type's. The actual organization of the data is dependent on the MPI process layout and work balance, not the data itself. Therefore, the type of data to be written does not play an important role, it is completely opaque. Yet, I need to use it a few times in MPI functions calls.
My function gets the data through a CLASS(*) dummy argument. MPI-functions are declared with a TYPE(*) dummy argument. Here is a small reproducer of my problem:
MODULE test_mod
USE, INTRINSIC :: ISO_FORTRAN_ENV
USE MPI_f08
IMPLICIT NONE (type, external)
CONTAINS
SUBROUTINE test(a)
! Subroutine argument
CLASS(*), INTENT(inout) :: a
! Local variables
INTEGER(int32) :: nprocs
TYPE(MPI_Datatype) :: mpi_dtype
CLASS(*), ALLOCATABLE :: datalist(:)
CALL MPI_Comm_size(MPI_COMM_WORLD, nprocs)
SELECT TYPE (a)
TYPE IS (INTEGER(int32))
mpi_dtype = MPI_INTEGER
ALLOCATE(INTEGER(kind=int32) :: datalist(nprocs))
TYPE IS (INTEGER(int64))
mpi_dtype = MPI_INTEGER8
ALLOCATE(INTEGER(kind=int64) :: datalist(nprocs))
TYPE IS (REAL(real32))
mpi_dtype = MPI_REAL
ALLOCATE(REAL(kind=real32) :: datalist(nprocs))
TYPE IS (REAL(real64))
mpi_dtype = MPI_DOUBLE_PRECISION
ALLOCATE(REAL(kind=real64) :: datalist(nprocs))
CLASS DEFAULT
ERROR STOP
END SELECT
CALL MPI_Allgather(a, 1, mpi_dtype, datalist, 1, mpi_dtype, &
MPI_COMM_WORLD)
END SUBROUTINE test
END MODULE test_mod
PROGRAM main
USE, INTRINSIC :: ISO_FORTRAN_ENV
USE test_mod
REAL :: var
INTEGER(int32) :: rank
CALL MPI_Init()
CALL MPI_Comm_rank(MPI_COMM_WORLD, rank)
var = REAL(rank, real32)
CALL test(var)
CALL MPI_Finalize()
END PROGRAM main
GFortran + OpenMPI compiles the example and runs it just fine.
Intel IFX + Intel MPI gives me the following error (mpiifort -fc=ifx test.F90):
test.F90(34): error #8769: If the actual argument is unlimited polymorphic, the corresponding dummy argument must also be unlimited polymorphic. [A]
CALL MPI_Allgather(a, 1, mpi_dtype, datalist, 1, mpi_dtype, &
---------------------------^
test.F90(34): error #8769: If the actual argument is unlimited polymorphic, the corresponding dummy argument must also be unlimited polymorphic. [DATALIST]
CALL MPI_Allgather(a, 1, mpi_dtype, datalist, 1, mpi_dtype, &
--------------------------------------------^
test.F90(42): error #7002: Error in opening the compiled module file. Check INCLUDE paths. [TEST_MOD]
USE test_mod
--------^
compilation aborted for test.F90 (code 1)
In this example I ditched the user-defined types in the allowed inputs to simplify.
I thought originally that I would post the problem over in the HPC-forum, however, I believe it is more a compiler issue than an MPI issue.
How to deal with the situation? A solution is of course to use the following:
SELECT TYPE (a)
TYPE IS (INTEGER(int32))
SELECT TYPE (datalist)
TYPE IS (INTEGER(int32))
CALL MPI_Allgather(a, 1, mpi_dtype, datalist, 1, mpi_dtype, &
MPI_COMM_WORLD)
END SELECT
TYPE IS (INTEGER(int64))
SELECT TYPE (datalist)
TYPE IS (INTEGER(int64))
CALL MPI_Allgather(a, 1, mpi_dtype, datalist, 1, mpi_dtype, &
MPI_COMM_WORLD)
END SELECT
TYPE IS (REAL(real32))
SELECT TYPE (datalist)
TYPE IS (REAL(real32))
CALL MPI_Allgather(a, 1, mpi_dtype, datalist, 1, mpi_dtype, &
MPI_COMM_WORLD)
END SELECT
TYPE IS (REAL(real64))
SELECT TYPE (datalist)
TYPE IS (REAL(real64))
CALL MPI_Allgather(a, 1, mpi_dtype, datalist, 1, mpi_dtype, &
MPI_COMM_WORLD)
END SELECT
CLASS DEFAULT
ERROR STOP
END SELECT
But this is just complete crazy spaghetti. It certainly doesn't look pretty, it certainly does not easily scale to even more accepted types and certainly is not particular friendly to the developer in any particular way. It does compile, though...
Does the Intel Fortran compiler have any options in reducing the strictness it enforces in this situation? Do any of you have any clues or hints?
Compiler and MPI versions:
$ mpiifort -fc=ifx -v
mpiifort for the Intel(R) MPI Library 2021.9 for Linux*
Copyright Intel Corporation.
ifx version 2023.1.0
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
That faulty error message is gone with the last week's releases of ifx and ifort. Please check out the 2024.1 release.
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I think the Intel compiler is wrong here. Both CLASS(*) and TYPE(*) entities are unlimited polymorphic. and it is allowed to pass a CLASS(*) to a TYPE(*). I note that NAG Fortran also allows this combination.
Here's an even simpler reproducer:
subroutine test (baz)
implicit none
interface
subroutine foo (a)
type(*) :: a
end subroutine foo
end interface
class(*) :: baz
call foo (baz)
end subroutine test
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thanks for reporting this, @hakostra1. Thanks, @Steve_Lionel, for the excellent reproducer.
Bug filed, CMPLRLLVM-48770.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thanks for the reply both of you. I have temporarily mitigated the problem by switching from "USE MPI_f08" to "USE MPI" in the problematic source file. Then it compiles with both GNU + OpenMPI and IFX + Intel MPI. However, I hope to switch back to the MPI_f08 module as soon as possible.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi,
I just installed and tested the new 2024.0 toolkits (base + hpc toolkit). Steve's example still does not compile:
$ ifx --version
ifx (IFX) 2024.0.0 20231017
Copyright (C) 1985-2023 Intel Corporation. All rights reserved.
$ ifx example.F90
example.F90(10): error #8769: If the actual argument is unlimited polymorphic, the corresponding dummy argument must also be unlimited polymorphic. [BAZ]
call foo (baz)
----------^
compilation aborted for example.F90 (code 1)
I had some hopes for 2024.0 on this one...
Any progress or plans to fix this one?
Thanks!
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
You're right. The fix missed the compiler code freeze date. I tested an early version of 2024.1. It's fixed there.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Right around the corner then, that is really awesome. I appreciate your effort.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
That faulty error message is gone with the last week's releases of ifx and ifort. Please check out the 2024.1 release.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Awesome, great!!
Big thanks to all of you in Intel for the great effort with IFX! You have really worked hard to iron out bugs for the last years, both IFX related and those that also affect ifort.This is of major importance for everyone working with Fortran. Keep up the good work!
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I'll let the Fortran compiler team know about your appreciation.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi again @Barbara_P_Intel and @Steve_Lionel
It turns out that the original code in post #1 of this thread still does not compile with ifx 2024.1. The simple reproducer by @Steve_Lionel does in fact compile with 2024.1.
I have created a simpler reproducer than the one in the original post that still does not compile:
SUBROUTINE test(baz, dtype)
USE MPI_f08
IMPLICIT NONE (type, external)
! Subroutine arguments
CLASS(*) :: baz
TYPE(MPI_Datatype) :: dtype
! Local variables
TYPE(MPI_Request) :: recvreq
CALL MPI_Irecv(baz, 1, dtype, 0, 0, MPI_COMM_SELF, recvreq)
END SUBROUTINE test
This fails with:
example-2.F90(12): error #8769: If the actual argument is unlimited polymorphic, the corresponding dummy argument must also be unlimited polymorphic. [BAZ]
CALL MPI_Irecv(baz, 1, dtype, 0, 0, MPI_COMM_SELF, recvreq)
-------------------^
compilation aborted for example-2.F90 (code 1)
This is using all 2024.1 oneAPI toolkits on Linux:
$ mpiifx --version
ifx (IFX) 2024.1.0 20240308
Copyright (C) 1985-2024 Intel Corporation. All rights reserved.
$ mpirun --version
Intel(R) MPI Library for Linux* OS, Version 2021.12 Build 20240213 (id: 4f55822)
Copyright 2003-2024, Intel Corporation.
Could this now be a problem with the MPI_f08 module instead of the compiler?
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
This could be an MPI problem since "USE MPI_f08" fails and "USE MPI" works.
Can you post this problem on the MPI Library Forum ? That's the best place for MPI discussion and questions.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
MPI_F08 has the interfaces written to use the TS29113 "Additional interoperability with C" features that are a part of Fortran 2018. Unfortunately, I don't see that Intel MPI ships the source to the module, which is unfortunate, so I can't see what the declaration of the routine is.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thanks for your comments. I will make a post in the MPI library forum.
The MPI standard give exactly how the binding should look like when using the MPI_f08:
MPI_Irecv(buf, count, datatype, source, tag, comm, request, ierror)
TYPE(*), DIMENSION(..), ASYNCHRONOUS :: buf
INTEGER, INTENT(IN) :: count, source, tag
TYPE(MPI_Datatype), INTENT(IN) :: datatype
TYPE(MPI_Comm), INTENT(IN) :: comm
TYPE(MPI_Request), INTENT(OUT) :: request
INTEGER, OPTIONAL, INTENT(OUT) :: ierror
Ref. MPI standard version 4.0 page 922.
The opaque objects like MPI_Datatype, MPI_Comm etc. are defined in chapter 251, page 18 of the same standard:
TYPE, BIND(C) :: MPI_Comm
INTEGER :: MPI_VAL
END TYPE MPI_Comm
and so on.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content

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