[Dart-dev] DART/branches Revision: 13119

dart at ucar.edu dart at ucar.edu
Mon Apr 22 13:37:38 MDT 2019


nancy at ucar.edu
2019-04-22 13:37:38 -0600 (Mon, 22 Apr 2019)
485
add code from cesm branch that supports an external
communicator passed in at init time.

consolidate the calls to the system() subroutine
since the form varies by compiler. remove replicated
code by consolidating where the optional initial string
(usually for a shell), and a trailing 0 for c-style 
termination is added. that code now occurs in a single place.

move all the mpi_reduce-related calls so they are
grouped together in a single code section.

doxygen-ize the comments.




Modified: DART/branches/rma_trunk/assimilation_code/modules/utilities/mpi_utilities_mod.f90
===================================================================
--- DART/branches/rma_trunk/assimilation_code/modules/utilities/mpi_utilities_mod.f90	2019-04-20 15:11:51 UTC (rev 13118)
+++ DART/branches/rma_trunk/assimilation_code/modules/utilities/mpi_utilities_mod.f90	2019-04-22 19:37:38 UTC (rev 13119)
@@ -41,6 +41,7 @@
 ! the NAG compiler needs these special definitions enabled
 
 ! !!NAG_BLOCK_EDIT START COMMENTED_OUT
+! !#ifdef __NAG__
 ! use F90_unix_proc, only : sleep, system, exit
  !! block for NAG compiler
  !  PURE SUBROUTINE SLEEP(SECONDS,SECLEFT)
@@ -55,6 +56,7 @@
  !  SUBROUTINE EXIT(STATUS)
  !    INTEGER,OPTIONAL :: STATUS
  !! end block
+!  !#endif
 ! !!NAG_BLOCK_EDIT END COMMENTED_OUT
 
 implicit none
@@ -71,6 +73,7 @@
 ! block below.  Please leave the BLOCK comment lines unchanged.
 
 ! !!SYSTEM_BLOCK_EDIT START COMMENTED_OUT
+! !#if .not. defined (__GFORTRAN__) .and. .not. defined(__NAG__)
 ! ! interface block for getting return code back from system() routine
 ! interface
 !  function system(string)
@@ -79,6 +82,7 @@
 !  end function system
 ! end interface
 ! ! end block
+! !#endif
 ! !!SYSTEM_BLOCK_EDIT END COMMENTED_OUT
 
 
@@ -109,10 +113,10 @@
           all_reduce_min_max  ! deprecated, replace by broadcast_minmax
 
 ! version controlled file description for error handling, do not edit
-character(len=256), parameter :: source   = &
+character(len=*), parameter :: source   = &
    "$URL$"
-character(len=32 ), parameter :: revision = "$Revision$"
-character(len=128), parameter :: revdate  = "$Date$"
+character(len=*), parameter :: revision = "$Revision$"
+character(len=*), parameter :: revdate  = "$Date$"
 
 logical :: module_initialized   = .false.
 
@@ -121,6 +125,8 @@
 integer :: head_task = 0         ! def 0, but N-1 if reverse_task_layout true
 logical :: print4status = .true. ! minimal messages for async4 handshake
 
+logical :: given_communicator = .false.   ! if communicator passed in, use it
+
 character(len = 256) :: errstring, errstring1
 
 ! for broadcasts, pack small messages into larger ones.  remember that the
@@ -165,7 +171,7 @@
 ! NAMELIST: change the following from .false. to .true. to enable
 ! the reading of this namelist.  This is the only place you need
 ! to make this change.
-logical :: use_namelist = .false.
+logical :: read_namelist = .false.
 
 namelist /mpi_utilities_nml/ reverse_task_layout, all_tasks_print, &
                              verbose, async2_verbose, async4_verbose, &
@@ -178,18 +184,21 @@
 ! mpi cover routines
 !-----------------------------------------------------------------------------
 
-subroutine initialize_mpi_utilities(progname, alternatename)
- character(len=*), intent(in), optional :: progname
- character(len=*), intent(in), optional :: alternatename
+!-----------------------------------------------------------------------------
 
+!> Initialize MPI and query it for global information.  Make a duplicate
+!> communicator so that any user code which wants to call MPI will not 
+!> interfere with any outstanding asynchronous requests, accidental tag
+!> matches, etc.  This routine must be called before any other routine in
+!> this file, and it should not be called more than once (but it does have
+!> defensive code in case that happens.)
 
-! Initialize MPI and query it for global information.  Make a duplicate
-! communicator so that any user code which wants to call MPI will not 
-! interfere with any outstanding asynchronous requests, accidental tag
-! matches, etc.  This routine must be called before any other routine in
-! this file, and it should not be called more than once (but it does have
-! defensive code in case that happens.)
+subroutine initialize_mpi_utilities(progname, alternatename, communicator)
 
+character(len=*), intent(in), optional :: progname
+character(len=*), intent(in), optional :: alternatename
+integer,          intent(in), optional :: communicator
+
 integer :: errcode, iunit
 logical :: already
 
@@ -200,6 +209,10 @@
    return


More information about the Dart-dev mailing list