[Dart-dev] DART/branches Revision: 13087

dart at ucar.edu dart at ucar.edu
Tue Mar 26 16:21:17 MDT 2019


nancy at ucar.edu
2019-03-26 16:21:17 -0600 (Tue, 26 Mar 2019)
201
bring more in line with the rma_trunk before trying to
merge.  some changes here should also migrate back to
the rma_trunk - better comments; doxygen style; option
to pass in an external communicator.



Modified: DART/branches/cesm_dart_esp/assimilation_code/modules/utilities/mpi_utilities_mod.f90
===================================================================
--- DART/branches/cesm_dart_esp/assimilation_code/modules/utilities/mpi_utilities_mod.f90	2019-03-26 16:39:04 UTC (rev 13086)
+++ DART/branches/cesm_dart_esp/assimilation_code/modules/utilities/mpi_utilities_mod.f90	2019-03-26 22:21:17 UTC (rev 13087)
@@ -39,25 +39,25 @@
 use mpi
 
 ! the NAG compiler needs these special definitions enabled
-! but we don't preprocess this file (why?) so you have to
-! edit this by hand for NAG.
 
-!#ifdef __NAG__
- !use F90_unix_proc, only : sleep, system, exit
- !! block for NAG compiler
- !  PURE SUBROUTINE SLEEP(SECONDS,SECLEFT)
- !    INTEGER,INTENT(IN) :: SECONDS
- !    INTEGER,OPTIONAL,INTENT(OUT) :: SECLEFT
- !
- !  SUBROUTINE SYSTEM(STRING,STATUS,ERRNO)
- !    CHARACTER*(*),INTENT(IN) :: STRING
- !    INTEGER,OPTIONAL,INTENT(OUT) :: STATUS,ERRNO
- !
- !!also used in exit_all outside this module
- !  SUBROUTINE EXIT(STATUS)
- !    INTEGER,OPTIONAL :: STATUS
- !! end block
-!#endif
+! !!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)
+!     INTEGER,INTENT(IN) :: SECONDS
+!     INTEGER,OPTIONAL,INTENT(OUT) :: SECLEFT
+! 
+!   SUBROUTINE SYSTEM(STRING,STATUS,ERRNO)
+!     CHARACTER*(*),INTENT(IN) :: STRING
+!     INTEGER,OPTIONAL,INTENT(OUT) :: STATUS,ERRNO
+! 
+! !also used in exit_all outside this module
+!   SUBROUTINE EXIT(STATUS)
+!     INTEGER,OPTIONAL :: STATUS
+! ! end block
+!  !#endif
+! !!NAG_BLOCK_EDIT END COMMENTED_OUT
 
 implicit none
 private
@@ -113,15 +113,15 @@
           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.
 
 character(len = 256) :: saved_progname = ''
-character(len = 256) :: shell_name = ''   ! if needed, add ksh, tcsh, bash, etc
+character(len = 128) :: shell_name = ''   ! if needed, add ksh, tcsh, bash, etc
 integer :: head_task = 0         ! def 0, but N-1 if reverse_task_layout true
 logical :: print4status = .true. ! minimal messages for async4 handshake
 
@@ -184,6 +184,8 @@
 ! mpi cover routines
 !-----------------------------------------------------------------------------
 
+!-----------------------------------------------------------------------------
+
 !> 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
@@ -226,10 +228,10 @@
 endif
 
 if (.not. present(communicator)) then
-! give this a temporary initial value, in case we call the abort code.
-! later down, we will dup the world comm and use a private comm for
-! our communication.
-my_local_comm = MPI_COMM_WORLD
+   ! give this a temporary initial value, in case we call the abort code.
+   ! later down, we will dup the world comm and use a private comm for
+   ! our communication.
+   my_local_comm = MPI_COMM_WORLD
 else
    my_local_comm = communicator
    given_communicator = .true.
@@ -259,6 +261,9 @@
    endif
 endif
 
+!> @todo FIXME this is in a funny place now.
+!> set module_initialized = .true. up higher, and
+!> just call register_module() here, no if() block..
 if ( .not. module_initialized ) then
    ! Initialize the module with utilities


More information about the Dart-dev mailing list