Skip to content

Commit 08523b5

Browse files
authored
search MPI runner in %MS_MPI% and PATH also in get_mpi_runner (#924)
2 parents c7c421a + c966c6b commit 08523b5

File tree

1 file changed

+20
-0
lines changed

1 file changed

+20
-0
lines changed

src/fpm_meta.f90

Lines changed: 20 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -838,6 +838,7 @@ subroutine get_mpi_runner(command,verbose,error)
838838
type(error_t), allocatable, intent(out) :: error
839839

840840
character(*), parameter :: try(*) = ['mpiexec ','mpirun ','mpiexec.exe','mpirun.exe ']
841+
character(:), allocatable :: bindir
841842
integer :: itri
842843
logical :: success
843844

@@ -855,6 +856,25 @@ subroutine get_mpi_runner(command,verbose,error)
855856
endif
856857
end do
857858

859+
! On windows, also search in %MSMPI_BIN%
860+
if (get_os_type()==OS_WINDOWS) then
861+
! Check that the runtime is installed
862+
bindir = ""
863+
call get_absolute_path(get_env('MSMPI_BIN'),bindir,error)
864+
if (verbose) print *, '+ %MSMPI_BIN%=',bindir
865+
! In some environments, variable %MSMPI_BIN% is missing (i.e. in GitHub Action images).
866+
! Do a second attempt: search for the default location
867+
if (len_trim(bindir)<=0 .or. allocated(error)) then
868+
if (verbose) print *, '+ %MSMPI_BIN% empty, searching C:\Program Files\Microsoft MPI\Bin\ ...'
869+
call get_absolute_path('C:\Program Files\Microsoft MPI\Bin\mpiexec.exe',bindir,error)
870+
endif
871+
if (len_trim(bindir)>0 .and. .not.allocated(error)) then
872+
! MSMPI_BIN directory found
873+
command%s = join_path(bindir,'mpiexec.exe')
874+
return
875+
endif
876+
endif
877+
858878
! No valid command found
859879
call fatal_error(error,'cannot find a valid mpi runner command')
860880
return

0 commit comments

Comments
 (0)