init_mpi Subroutine

public subroutine init_mpi(this, compiler, error)

Initialize MPI metapackage for the current system Cleanup

Get all candidate MPI wrappers No wrapper compiler fit. Are we on Windows? use MSMPI-specific search All attempts failed If there’s only an available Fortran wrapper, and the compiler’s different than fpm’s baseline fortran compiler suite, we still want to enable C language flags as that is most likely being ABI-compatible anyways. However, issues may arise. see e.g. Homebrew with clabng C/C++ and GNU fortran at https://gitlab.kitware.com/cmake/cmake/-/issues/18139 Initialize MPI package from wrapper command Request Fortran implicit typing Not all MPI implementations offer modules mpi and mpi_f08: hence, include them to the list of external modules, so they won’t be requested as standard source files

Arguments

Type IntentOptional Attributes Name
class(metapackage_t), intent(inout) :: this
type(compiler_t), intent(in) :: compiler
type(error_t), intent(out), allocatable :: error

Source Code

    subroutine init_mpi(this,compiler,error)
        class(metapackage_t), intent(inout) :: this
        type(compiler_t), intent(in) :: compiler
        type(error_t), allocatable, intent(out) :: error


        type(string_t), allocatable :: c_wrappers(:),cpp_wrappers(:),fort_wrappers(:)
        type(string_t) :: output,fwrap,cwrap,cxxwrap
        character(256) :: msg_out
        character(len=:), allocatable :: tokens(:)
        integer :: wcfit(3),mpilib(3),ic,icpp,i
        logical :: found

        !> Cleanup
        call destroy(this)

        !> Get all candidate MPI wrappers
        call mpi_wrappers(compiler,fort_wrappers,c_wrappers,cpp_wrappers)
        if (verbose) print 1, size(fort_wrappers),size(c_wrappers),size(cpp_wrappers)

        call wrapper_compiler_fit(fort_wrappers,c_wrappers,cpp_wrappers,compiler,wcfit,mpilib,error)

        if (allocated(error) .or. all(wcfit==0)) then

            !> No wrapper compiler fit. Are we on Windows? use MSMPI-specific search
            found = msmpi_init(this,compiler,error)
            if (allocated(error)) return

            !> All attempts failed
            if (.not.found) then
                call fatal_error(error,"cannot find MPI wrappers or libraries for "//compiler%name()//" compiler")
                return
            endif

        else

            if (wcfit(LANG_FORTRAN)>0) fwrap   = fort_wrappers(wcfit(LANG_FORTRAN))
            if (wcfit(LANG_C)>0)       cwrap   = c_wrappers   (wcfit(LANG_C))
            if (wcfit(LANG_CXX)>0)     cxxwrap = cpp_wrappers (wcfit(LANG_CXX))

            !> If there's only an available Fortran wrapper, and the compiler's different than fpm's baseline
            !> fortran compiler suite, we still want to enable C language flags as that is most likely being
            !> ABI-compatible anyways. However, issues may arise.
            !> see e.g. Homebrew with clabng C/C++ and GNU fortran at https://gitlab.kitware.com/cmake/cmake/-/issues/18139
            if (wcfit(LANG_FORTRAN)>0 .and. all(wcfit([LANG_C,LANG_CXX])==0)) then
                cwrap   = fort_wrappers(wcfit(LANG_FORTRAN))
                cxxwrap = fort_wrappers(wcfit(LANG_FORTRAN))
            end if

            if (verbose) print *, '+ MPI fortran wrapper: ',fwrap%s
            if (verbose) print *, '+ MPI c       wrapper: ',cwrap%s
            if (verbose) print *, '+ MPI c++     wrapper: ',cxxwrap%s

            !> Initialize MPI package from wrapper command
            call init_mpi_from_wrappers(this,compiler,mpilib(LANG_FORTRAN),fwrap,cwrap,cxxwrap,error)
            if (allocated(error)) return

            !> Request Fortran implicit typing
            if (mpilib(LANG_FORTRAN)/=MPI_TYPE_INTEL) then
                allocate(this%fortran)
                this%fortran%implicit_typing   = .true.
                this%fortran%implicit_external = .true.
            endif

        end if

        !> Not all MPI implementations offer modules mpi and mpi_f08: hence, include them
        !> to the list of external modules, so they won't be requested as standard source files
        this%has_external_modules = .true.
        this%external_modules = [string_t("mpi"),string_t("mpi_f08")]

        1 format('MPI wrappers found: fortran=',i0,' c=',i0,' c++=',i0)

    end subroutine init_mpi