Ignore:
Timestamp:
Mar 20, 2014 8:40:49 AM (11 years ago)
Author:
raasch
Message:

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

File:
1 edited

Legend:

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

    r1310 r1320  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! ONLY-attribute added to USE-statements,
     23! kind-parameters added to all INTEGER and REAL declaration statements,
     24! kinds are defined in new module kinds,
     25! revision history before 2012 removed,
     26! comment fields (!:) to be used for variable explanations added to
     27! all variable declaration statements
    2328!
    2429! Former revisions:
     
    3237! minor reformatting
    3338!
    34 ! 667 2010-12-23 12:06:00Z suehring/gryschka
    35 ! Exchange of terminate_coupled between ocean and atmosphere by PE0
    36 !
    37 ! 622 2010-12-10 08:08:13Z raasch
    38 ! optional barriers included in order to speed up collective operations
    39 !
    40 ! 291 2009-04-16 12:07:26Z raasch
    41 ! Coupling with independent precursor runs.
    42 ! Output of messages replaced by message handling routine
    43 !
    44 ! 222 2009-01-12 16:04:16Z letzel
    45 ! Implementation of an MPI-1 coupling: replaced myid with target_id
    46 ! Bugfix for nonparallel execution
    47 !
    48 ! 108 2007-08-24 15:10:38Z letzel
    49 ! modifications to terminate coupled runs
    50 !
    51 ! RCS Log replace by Id keyword, revision history cleaned up
    52 !
    53 ! Revision 1.11  2007/02/11 12:55:13  raasch
    54 ! Informative output to the job protocol
    55 !
    5639! Revision 1.1  1998/03/18 20:06:51  raasch
    5740! Initial revision
     
    6447!------------------------------------------------------------------------------!
    6548
     49    USE control_parameters,                                                    &
     50        ONLY:  coupling_mode, dt_restart, end_time, message_string,            &
     51               run_description_header, simulated_time, terminate_coupled,      &
     52               terminate_coupled_remote, terminate_run,                        &
     53               termination_time_needed, time_restart,                          &
     54               time_since_reference_point, write_binary
     55    USE kinds
    6656    USE pegrid
    67     USE control_parameters
    6857
    6958    IMPLICIT NONE
    7059
    7160
    72     LOGICAL :: terminate_run_l
    73     REAL ::  remaining_time
     61    LOGICAL :: terminate_run_l  !:
     62
     63    REAL(wp) ::  remaining_time !:
    7464
    7565
     
    8171!-- If necessary set a flag to stop the model run
    8272    terminate_run_l = .FALSE.
    83     IF ( remaining_time <= termination_time_needed  .AND. &
     73    IF ( remaining_time <= termination_time_needed  .AND.                      &
    8474         write_binary(1:4) == 'true' )  THEN
    8575
     
    9282!-- one processor has reached the time limit.
    9383    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    94     CALL MPI_ALLREDUCE( terminate_run_l, terminate_run, 1, MPI_LOGICAL, &
     84    CALL MPI_ALLREDUCE( terminate_run_l, terminate_run, 1, MPI_LOGICAL,        &
    9585                        MPI_LOR, comm2d, ierr )
    9686#else
     
    10191!-- Output that job will be terminated
    10292    IF ( terminate_run  .AND.  myid == 0 )  THEN
    103        WRITE( message_string, * ) 'run will be terminated because it is ', &
    104                        'running out of job cpu limit & ',                  &
    105                        'remaining time:         ', remaining_time, ' s',   &
     93       WRITE( message_string, * ) 'run will be terminated because it is ',     &
     94                       'running out of job cpu limit & ',                      &
     95                       'remaining time:         ', remaining_time, ' s',       &
    10696                       'termination time needed:', termination_time_needed, ' s'
    10797       CALL message( 'check_for_restart', 'PA0163', 0, 1, 0, 6, 0 )
     
    113103!-- informed of another termination reason (terminate_coupled > 0) before,
    114104!-- or vice versa (terminate_coupled_remote > 0).
    115     IF ( terminate_run .AND. TRIM( coupling_mode ) /= 'uncoupled'  .AND. &
     105    IF ( terminate_run .AND. TRIM( coupling_mode ) /= 'uncoupled'  .AND.       &
    116106         terminate_coupled == 0  .AND.  terminate_coupled_remote == 0 )  THEN
    117107
     
    125115                             comm_inter, status, ierr )
    126116       ENDIF
    127        CALL MPI_BCAST( terminate_coupled_remote, 1, MPI_INTEGER, 0, comm2d,  &
     117       CALL MPI_BCAST( terminate_coupled_remote, 1, MPI_INTEGER, 0, comm2d,    &
    128118                       ierr )
    129119#endif
     
    132122!
    133123!-- Set the stop flag also, if restart is forced by user
    134     IF ( time_restart /= 9999999.9  .AND.  &
     124    IF ( time_restart /= 9999999.9  .AND.                                      &
    135125         time_restart < time_since_reference_point )  THEN
    136126
     
    149139          ENDIF
    150140
    151           WRITE( message_string, * ) 'run will be terminated due to user ', &
    152                                   'settings of',                            &
    153                                   '&restart_time / dt_restart',             &
     141          WRITE( message_string, * ) 'run will be terminated due to user ',    &
     142                                  'settings of',                               &
     143                                  '&restart_time / dt_restart',                &
    154144                                  '&new restart time is: ', time_restart, ' s'
    155145          CALL message( 'check_for_restart', 'PA0164', 0, 0, 0, 6, 0 )
     
    160150!--       informed of another termination reason (terminate_coupled > 0) before,
    161151!--       or vice versa (terminate_coupled_remote > 0).
    162           IF ( coupling_mode /= 'uncoupled' .AND. terminate_coupled == 0  &
     152          IF ( coupling_mode /= 'uncoupled' .AND. terminate_coupled == 0       &
    163153               .AND.  terminate_coupled_remote == 0 )  THEN
    164154
     
    176166                                   comm_inter, status, ierr )   
    177167             ENDIF
    178              CALL MPI_BCAST( terminate_coupled_remote, 1, MPI_INTEGER, 0,  &
     168             CALL MPI_BCAST( terminate_coupled_remote, 1, MPI_INTEGER, 0,      &
    179169                             comm2d, ierr ) 
    180170#endif
Note: See TracChangeset for help on using the changeset viewer.