Skip to content

Commit

Permalink
Filter out unnecessary MPI flags; add MSMPI_BIN to Git-Bash PATH
Browse files Browse the repository at this point in the history
This reverts commit 0897659.

filter unnecessary build and linker flags from mpi wrappers

add Git-Bash style path to Windows metapackage CI

cleanup

update Intel compilers

Update fpm_meta.f90
  • Loading branch information
perazz committed Dec 13, 2023
1 parent 4c1a93f commit 6114333
Show file tree
Hide file tree
Showing 3 changed files with 145 additions and 20 deletions.
1 change: 1 addition & 0 deletions .github/workflows/meta.yml
Original file line number Diff line number Diff line change
Expand Up @@ -152,6 +152,7 @@ jobs:
if: contains(matrix.os,'windows') && contains(matrix.mpi,'msmpi')
run: |
echo "C:\Program Files\Microsoft MPI\Bin\" | Out-File -FilePath $env:GITHUB_PATH -Encoding utf8 -Append
echo "/c/Program Files/Microsoft MPI/Bin/" | Out-File -FilePath $env:GITHUB_PATH -Encoding utf8 -Append
echo "MSMPI_BIN=C:\Program Files\Microsoft MPI\Bin\" | Out-File -FilePath $env:GITHUB_ENV -Append
- name: (Windows) load OneAPI environment variables
Expand Down
2 changes: 2 additions & 0 deletions fpm.toml
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,8 @@ fortran-regex.git = "https://github.com/perazz/fortran-regex"
fortran-regex.tag = "1.1.2"
jonquil.git = "https://github.com/toml-f/jonquil"
jonquil.rev = "4fbd4cf34d577c0fd25e32667ee9e41bf231ece8"
fortran-shlex.git = "https://github.com/perazz/fortran-shlex"
fortran-shlex.tag = "1.0.1"

[[test]]
name = "cli-test"
Expand Down
162 changes: 142 additions & 20 deletions src/fpm_meta.f90
Original file line number Diff line number Diff line change
Expand Up @@ -3,21 +3,22 @@
!> This is a wrapper data type that encapsulate all pre-processing information
!> (compiler flags, linker libraries, etc.) required to correctly enable a package
!> to use a core library.
!>
!>
!>### Available core libraries
!>
!>### Available core libraries
!>
!> - OpenMP
!> - MPI
!> - fortran-lang stdlib
!> - fortran-lang minpack
!>
!>
!>
!> @note Core libraries are enabled in the [build] section of the fpm.toml manifest
!>
!>
module fpm_meta
use fpm_strings, only: string_t, len_trim, remove_newline_characters
use fpm_strings, only: string_t, len_trim, remove_newline_characters, str_begins_with_str, &
str_ends_with
use fpm_error, only: error_t, fatal_error, syntax_error, fpm_stop
use fpm_compiler
use fpm_model
Expand All @@ -29,6 +30,8 @@ module fpm_meta
use fpm_filesystem, only: run, get_temp_filename, getline, exists, canon_path, is_dir, get_dos_path
use fpm_versioning, only: version_t, new_version, regex_version_from_text
use fpm_os, only: get_absolute_path
use shlex_module, only: shlex_split => split
use regex_module, only: regex
use iso_fortran_env, only: stdout => output_unit

implicit none
Expand Down Expand Up @@ -434,10 +437,8 @@ subroutine resolve_metapackage_model(model,package,settings,error)
! Dependencies are added to the package config, so they're properly resolved
! into the dependency tree later.
! Flags are added to the model (whose compiler needs to be already initialized)
if (model%compiler%is_unknown()) then
call fatal_error(error,"compiler not initialized: cannot build metapackages")
return
end if
if (model%compiler%is_unknown()) &
write(stdout,'(a)') '<WARNING> compiler not initialized: metapackages may not be available'

! OpenMP
if (package%meta%openmp%on) then
Expand Down Expand Up @@ -983,28 +984,26 @@ subroutine init_mpi_from_wrappers(this,compiler,mpilib,fort_wrapper,c_wrapper,cx
call destroy(this)

! Get linking flags
if (mpilib/=MPI_TYPE_INTEL) then
this%link_flags = mpi_wrapper_query(mpilib,fort_wrapper,'link',verbose,error)
if (mpilib/=MPI_TYPE_INTEL) &
this%link_flags = mpi_wrapper_query(mpilib,fort_wrapper,'link',verbose,error)
if (allocated(error)) return

! We fix OpenMPI's Fortran wrapper bug (https://github.com/open-mpi/ompi/issues/11636)
!call fix_openmpi_link_flags(this%link_flags,compiler,mpilib,fort_wrapper,c_wrapper,cxx_wrapper,error)
! Remove useless/dangerous flags
call filter_link_arguments(compiler,this%link_flags)

if (allocated(error)) return
this%has_link_flags = len_trim(this%link_flags)>0
endif
this%has_link_flags = len_trim(this%link_flags)>0

! Request to use libs in arbitrary order
if (this%has_link_flags .and. compiler%is_gnu() .and. os_is_unix() .and. get_os_type()/=OS_MACOS) then
this%link_flags = string_t(' -Wl,--start-group '//this%link_flags%s)
end if


! Add language-specific flags
call set_language_flags(mpilib,fort_wrapper,this%has_fortran_flags,this%fflags,verbose,error)
call set_language_flags(compiler,mpilib,fort_wrapper,this%has_fortran_flags,this%fflags,verbose,error)
if (allocated(error)) return
call set_language_flags(mpilib,c_wrapper,this%has_c_flags,this%cflags,verbose,error)
call set_language_flags(compiler,mpilib,c_wrapper,this%has_c_flags,this%cflags,verbose,error)
if (allocated(error)) return
call set_language_flags(mpilib,cxx_wrapper,this%has_cxx_flags,this%cxxflags,verbose,error)
call set_language_flags(compiler,mpilib,cxx_wrapper,this%has_cxx_flags,this%cxxflags,verbose,error)
if (allocated(error)) return

! Get library version
Expand All @@ -1021,7 +1020,8 @@ subroutine init_mpi_from_wrappers(this,compiler,mpilib,fort_wrapper,c_wrapper,cx

contains

subroutine set_language_flags(mpilib,wrapper,has_flags,flags,verbose,error)
subroutine set_language_flags(compiler,mpilib,wrapper,has_flags,flags,verbose,error)
type(compiler_t), intent(in) :: compiler
integer, intent(in) :: mpilib
type(string_t), intent(in) :: wrapper
logical, intent(inout) :: has_flags
Expand All @@ -1041,6 +1041,8 @@ subroutine set_language_flags(mpilib,wrapper,has_flags,flags,verbose,error)

if (verbose) print *, '+ MPI language flags from wrapper <',wrapper%s,'>: flags=',flags%s

call filter_build_arguments(compiler,flags)

endif

end subroutine set_language_flags
Expand Down Expand Up @@ -1598,4 +1600,124 @@ type(string_t) function mpi_wrapper_query(mpilib,wrapper,command,verbose,error)

end function mpi_wrapper_query

!> Check if input is a useful linker argument
logical function is_link_argument(compiler,string)
type(compiler_t), intent(in) :: compiler
character(*), intent(in) :: string

select case (compiler%id)
case (id_intel_classic_windows,id_intel_llvm_windows)
is_link_argument = string=='/link' &
.or. str_begins_with_str(string,'/LIBPATH')&
.or. str_ends_with(string,'.lib') ! always .lib whether static or dynamic
case default

! fix OpenMPI's Fortran wrapper bug (https://github.com/open-mpi/ompi/issues/11636) here
is_link_argument = ( str_begins_with_str(string,'-L') &
.or. str_begins_with_str(string,'-l') &
.or. str_begins_with_str(string,'-Xlinker') &
.or. string=='-pthread' &
.or. (str_begins_with_str(string,'-W') .and. &
(string/='-Wall') .and. (.not.str_begins_with_str(string,'-Werror'))) ) &
.and. .not. ( &
(get_os_type()==OS_MACOS .and. index(string,'-commons,use_dylibs')>0) &
)
end select

end function is_link_argument

!> From the build flags, remove optimization and other unnecessary flags
subroutine filter_build_arguments(compiler,command)
type(compiler_t), intent(in) :: compiler
type(string_t), intent(inout) :: command
character(len=:), allocatable :: tokens(:)

integer :: i,n,re_i,re_l
logical, allocatable :: keep(:)
logical :: keep_next
character(len=:), allocatable :: module_flag,include_flag

if (len_trim(command)<=0) return

! Split command into arguments
tokens = shlex_split(command%s)

module_flag = get_module_flag(compiler,"")
include_flag = get_include_flag(compiler,"")

n = size(tokens)
allocate(keep(n),source=.false.)
keep_next = .false.

do i=1,n

if (get_os_type()==OS_MACOS .and. index(tokens(i),'-commons,use_dylibs')>0) then
keep(i) = .false.
keep_next = .false.
elseif (str_begins_with_str(tokens(i),'-D') .or. &
str_begins_with_str(tokens(i),'-f') .or. &
str_begins_with_str(tokens(i),'-I') .or. &
str_begins_with_str(tokens(i),module_flag) .or. &
str_begins_with_str(tokens(i),include_flag) .or. &
tokens(i)=='-pthread' .or. &
(str_begins_with_str(tokens(i),'-W') .and. tokens(i)/='-Wall' .and. .not.str_begins_with_str(tokens(i),'-Werror')) &
) then
keep(i) = .true.
if (tokens(i)==module_flag .or. tokens(i)==include_flag .or. tokens(i)=='-I') keep_next = .true.
elseif (keep_next) then
keep(i) = .true.
keep_next = .false.
end if
end do

! Backfill
command = string_t("")
do i=1,n
if (.not.keep(i)) cycle

command%s = command%s//' '//trim(tokens(i))
end do


end subroutine filter_build_arguments

!> From the linker flags, remove optimization and other unnecessary flags
subroutine filter_link_arguments(compiler,command)
type(compiler_t), intent(in) :: compiler
type(string_t), intent(inout) :: command
character(len=:), allocatable :: tokens(:)

integer :: i,n
logical, allocatable :: keep(:)
logical :: keep_next

if (len_trim(command)<=0) return

! Split command into arguments
tokens = shlex_split(command%s)

n = size(tokens)
allocate(keep(n),source=.false.)
keep_next = .false.

do i=1,n
if (is_link_argument(compiler,tokens(i))) then
keep(i) = .true.
if (tokens(i)=='-L' .or. tokens(i)=='-Xlinker') keep_next = .true.
elseif (keep_next) then
keep(i) = .true.
keep_next = .false.
end if
end do

! Backfill
command = string_t("")
do i=1,n
if (.not.keep(i)) cycle
command%s = command%s//' '//trim(tokens(i))
end do

end subroutine filter_link_arguments


end module fpm_meta

0 comments on commit 6114333

Please sign in to comment.