Skip to content

Commit

Permalink
polish screen output
Browse files Browse the repository at this point in the history
  • Loading branch information
perazz committed Dec 13, 2023
1 parent 0015458 commit 2f2e252
Showing 1 changed file with 6 additions and 6 deletions.
12 changes: 6 additions & 6 deletions src/fpm_meta.f90
Original file line number Diff line number Diff line change
Expand Up @@ -103,12 +103,14 @@ module fpm_meta
public :: MPI_TYPE_NAME

!> Debugging information
logical, parameter, private :: verbose = .true.
logical, parameter, private :: verbose = .false.

integer, parameter, private :: LANG_FORTRAN = 1
integer, parameter, private :: LANG_C = 2
integer, parameter, private :: LANG_CXX = 3

character(*), parameter :: LANG_NAME(*) = [character(7) :: 'Fortran','C','C++']

contains

!> Return a name for the MPI library
Expand Down Expand Up @@ -1074,19 +1076,17 @@ subroutine mpi_compiler_match(language,wrappers,compiler,which_one,mpilib,error)
same_vendor = 0
mpilib = MPI_TYPE_NONE

if (verbose) print *, '+ Trying to match available ',LANG_NAME(language),' MPI wrappers to ',compiler%fc,'...'

do i=1,size(wrappers)

mpilib = which_mpi_library(wrappers(i),compiler,verbose=.false.)

screen = mpi_wrapper_query(mpilib,wrappers(i),'compiler',verbose=.false.,error=error)

print *, 'mpi wrapper ',wrappers(i)%s,' lib=',MPI_TYPE_NAME(mpilib),' compiler=',screen%s,&
' current=',compiler%fc,compiler%cc,compiler%cxx
if (allocated(error)) print *, ' error=',error%message

if (allocated(error)) return

if (verbose) print *, ' Wrapper ',wrappers(i)%s,' lib=',MPI_TYPE_NAME(mpilib),' uses ',screen%s

select case (language)
case (LANG_FORTRAN)
! Build compiler type. The ID is created based on the Fortran name
Expand Down

0 comments on commit 2f2e252

Please sign in to comment.