Skip to content

Commit

Permalink
manual icc -> icx match
Browse files Browse the repository at this point in the history
  • Loading branch information
perazz committed Dec 13, 2023
1 parent 295991e commit 14d4743
Showing 1 changed file with 28 additions and 3 deletions.
31 changes: 28 additions & 3 deletions src/fpm_meta.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1063,13 +1063,15 @@ subroutine mpi_compiler_match(language,wrappers,compiler,which_one,mpilib,error)
integer, intent(out) :: which_one, mpilib
type(error_t), allocatable, intent(out) :: error

integer :: i
integer :: i, same_vendor, vendor_mpilib
type(string_t) :: screen
character(128) :: msg_out
type(compiler_t) :: mpi_compiler

which_one = 0
mpilib = MPI_TYPE_NONE
which_one = 0
same_vendor = 0
mpilib = MPI_TYPE_NONE


do i=1,size(wrappers)

Expand All @@ -1093,17 +1095,40 @@ subroutine mpi_compiler_match(language,wrappers,compiler,which_one,mpilib,error)
return
end if

! Because the intel mpi library does not support llvm_ compiler wrappers yet,
! we must check for that manually
if (mpi_compiler%is_intel() .and. compiler%is_intel()) then
which_one = i
return
end if

case (LANG_C)
! For other languages, we can only hope that the name matches the expected one
if (screen%s==compiler%cc .or. screen%s==compiler%fc) then
which_one = i
return
end if

! Because the intel mpi library does not support llvm_ compiler wrappers yet,
! we must check for that manually
if (screen%s='icc' .and. compiler%cc=='icx') then
which_one = i
return
end if

case (LANG_CXX)
if (screen%s==compiler%cxx .or. screen%s==compiler%fc) then
which_one = i
return
end if

! Because the intel mpi library does not support llvm_ compiler wrappers yet,
! we must check for that manually
if (screen%s='icpc' .and. compiler%cc=='icpx') then
which_one = i
return
end if

end select

end do
Expand Down

0 comments on commit 14d4743

Please sign in to comment.