Skip to content

Commit c9072d9

Browse files
authored
MPI: add mpi and mpi_f08 to the list of external modules (#930)
2 parents b20b3dc + c80cdfd commit c9072d9

File tree

1 file changed

+31
-20
lines changed

1 file changed

+31
-20
lines changed

src/fpm_meta.f90

+31-20
Original file line numberDiff line numberDiff line change
@@ -39,15 +39,16 @@ module fpm_meta
3939
!> Package version (if supported)
4040
type(version_t), allocatable :: version
4141

42-
logical :: has_link_libraries = .false.
43-
logical :: has_link_flags = .false.
44-
logical :: has_build_flags = .false.
45-
logical :: has_fortran_flags = .false.
46-
logical :: has_c_flags = .false.
47-
logical :: has_cxx_flags = .false.
48-
logical :: has_include_dirs = .false.
49-
logical :: has_dependencies = .false.
50-
logical :: has_run_command = .false.
42+
logical :: has_link_libraries = .false.
43+
logical :: has_link_flags = .false.
44+
logical :: has_build_flags = .false.
45+
logical :: has_fortran_flags = .false.
46+
logical :: has_c_flags = .false.
47+
logical :: has_cxx_flags = .false.
48+
logical :: has_include_dirs = .false.
49+
logical :: has_dependencies = .false.
50+
logical :: has_run_command = .false.
51+
logical :: has_external_modules = .false.
5152

5253
!> List of compiler flags and options to be added
5354
type(string_t) :: flags
@@ -58,6 +59,7 @@ module fpm_meta
5859
type(string_t) :: run_command
5960
type(string_t), allocatable :: incl_dirs(:)
6061
type(string_t), allocatable :: link_libs(:)
62+
type(string_t), allocatable :: external_modules(:)
6163

6264
!> Special fortran features
6365
type(fortran_features_t), allocatable :: fortran
@@ -120,15 +122,16 @@ end function MPI_TYPE_NAME
120122
elemental subroutine destroy(this)
121123
class(metapackage_t), intent(inout) :: this
122124

123-
this%has_link_libraries = .false.
124-
this%has_link_flags = .false.
125-
this%has_build_flags = .false.
126-
this%has_fortran_flags = .false.
127-
this%has_c_flags = .false.
128-
this%has_cxx_flags = .false.
129-
this%has_include_dirs = .false.
130-
this%has_dependencies = .false.
131-
this%has_run_command = .false.
125+
this%has_link_libraries = .false.
126+
this%has_link_flags = .false.
127+
this%has_build_flags = .false.
128+
this%has_fortran_flags = .false.
129+
this%has_c_flags = .false.
130+
this%has_cxx_flags = .false.
131+
this%has_include_dirs = .false.
132+
this%has_dependencies = .false.
133+
this%has_run_command = .false.
134+
this%has_external_modules = .false.
132135

133136
if (allocated(this%fortran)) deallocate(this%fortran)
134137
if (allocated(this%version)) deallocate(this%version)
@@ -141,6 +144,7 @@ elemental subroutine destroy(this)
141144
if (allocated(this%link_libs)) deallocate(this%link_libs)
142145
if (allocated(this%dependency)) deallocate(this%dependency)
143146
if (allocated(this%incl_dirs)) deallocate(this%incl_dirs)
147+
if (allocated(this%external_modules)) deallocate(this%external_modules)
144148

145149
end subroutine destroy
146150

@@ -327,6 +331,10 @@ subroutine resolve_model(self,model,error)
327331
model%include_dirs = [model%include_dirs,self%incl_dirs]
328332
end if
329333

334+
if (self%has_external_modules) then
335+
model%external_modules = [model%external_modules,self%external_modules]
336+
end if
337+
330338
end subroutine resolve_model
331339

332340
subroutine resolve_package_config(self,package,error)
@@ -467,11 +475,9 @@ subroutine init_mpi(this,compiler,error)
467475
integer :: wcfit(3),mpilib(3),ic,icpp,i
468476
logical :: found
469477

470-
471478
!> Cleanup
472479
call destroy(this)
473480

474-
475481
!> Get all candidate MPI wrappers
476482
call mpi_wrappers(compiler,fort_wrappers,c_wrappers,cpp_wrappers)
477483
if (verbose) print 1, size(fort_wrappers),size(c_wrappers),size(cpp_wrappers)
@@ -522,6 +528,11 @@ subroutine init_mpi(this,compiler,error)
522528

523529
end if
524530

531+
!> Not all MPI implementations offer modules mpi and mpi_f08: hence, include them
532+
!> to the list of external modules, so they won't be requested as standard source files
533+
this%has_external_modules = .true.
534+
this%external_modules = [string_t("mpi"),string_t("mpi_f08")]
535+
525536
1 format('MPI wrappers found: fortran=',i0,' c=',i0,' c++=',i0)
526537

527538
end subroutine init_mpi

0 commit comments

Comments
 (0)