Ignore:
Timestamp:
Mar 21, 2016 4:50:28 PM (8 years ago)
Author:
raasch
Message:

Introduction of different data transfer modes; restart mechanism adjusted for nested runs; parameter consistency checks for nested runs; further formatting cleanup

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/check_for_restart.f90

    r1683 r1797  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! check now accounts for nesting mode
    2222!
    2323! Former revisions:
     
    7070               termination_time_needed, time_restart,                          &
    7171               time_since_reference_point, write_binary
     72
    7273    USE kinds
     74
    7375    USE pegrid
    7476
     77    USE pmc_interface,                                                         &
     78        ONLY:  comm_world_nesting, cpl_id, nested_run
     79
    7580    IMPLICIT NONE
    7681
    77 
    78     LOGICAL :: terminate_run_l           !<
    79     LOGICAL :: do_stop_now = .FALSE.     !<
    80     LOGICAL :: do_restart_now = .FALSE.  !<
     82    INTEGER ::  global_communicator       !< global communicator to be used here
     83
     84    LOGICAL ::  terminate_run_l           !<
     85    LOGICAL ::  do_stop_now = .FALSE.     !<
     86    LOGICAL ::  do_restart_now = .FALSE.  !<
    8187
    8288    REAL(wp) ::  remaining_time !<
     
    96102    ENDIF
    97103
     104!
     105!-- Set the global communicator to be used (depends on the mode in which PALM is
     106!-- running)
     107    IF ( nested_run )  THEN
     108       global_communicator = comm_world_nesting
     109    ELSE
     110       global_communicator = comm2d
     111    ENDIF
     112
    98113#if defined( __parallel )
    99114!
    100115!-- Make a logical OR for all processes. Stop the model run if at least
    101 !-- one processor has reached the time limit.
    102     IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    103     CALL MPI_ALLREDUCE( terminate_run_l, terminate_run, 1, MPI_LOGICAL,        &
    104                         MPI_LOR, comm2d, ierr )
     116!-- one process has reached the time limit.
     117    IF ( collective_wait )  CALL MPI_BARRIER( global_communicator, ierr )
     118    CALL MPI_ALLREDUCE( terminate_run_l, terminate_run, 1, MPI_LOGICAL,     &
     119                        MPI_LOR, global_communicator, ierr )
    105120#else
    106121    terminate_run = terminate_run_l
     
    164179#if defined( __parallel )
    165180!
    166 !-- Make a logical OR for all processes. Stop the model run if at least
    167 !-- one processor has reached the time limit.
    168     IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
     181!-- Make a logical OR for all processes. Stop the model run if a flag file has
     182!-- been detected above.
     183    IF ( collective_wait )  CALL MPI_BARRIER( global_communicator, ierr )
    169184    CALL MPI_ALLREDUCE( terminate_run_l, terminate_run, 1, MPI_LOGICAL,        &
    170                         MPI_LOR, comm2d, ierr )
     185                        MPI_LOR, global_communicator, ierr )
    171186#else
    172187    terminate_run = terminate_run_l
     
    256271!-- the start of a continuation run, except if the user forced to stop the
    257272!-- run without restart
    258     IF ( terminate_run  .AND.  myid == 0 .AND. .NOT. do_stop_now)  THEN
     273    IF ( terminate_run  .AND.  myid == 0  .AND.  cpl_id == 1  .AND.            &
     274         .NOT. do_stop_now)  THEN
    259275
    260276       OPEN ( 90, FILE='CONTINUE_RUN', FORM='FORMATTED' )
Note: See TracChangeset for help on using the changeset viewer.