Ignore:
Timestamp:
Aug 24, 2007 3:10:38 PM (17 years ago)
Author:
letzel
Message:
  • Improved coupler: evaporation - salinity-flux coupling for humidity = .T.,

avoid MPI hangs when coupled runs terminate, add DOC/app/chapter_3.8;

  • Optional calculation of km and kh from initial TKE e_init;
  • Default initialization of km,kh = 0.00001 for ocean = .T.;
  • Allow data_output_pr= q, wq, w"q", w*q* for humidity = .T.;
  • Bugfix: Rayleigh damping for ocean fixed.
File:
1 edited

Legend:

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

    r4 r108  
    44! Actual revisions:
    55! -----------------
     6! modifications to terminate coupled runs
    67!
    78!
     
    2425
    2526    USE pegrid
     27    USE control_parameters
    2628
    2729#if defined( __parallel )
    28     CALL MPI_FINALIZE( ierr )
    29 #endif
     30    IF ( coupling_mode == 'uncoupled' )  THEN
     31       CALL MPI_FINALIZE( ierr )
     32    ELSE
     33
     34       SELECT CASE ( terminate_coupled_remote )
     35
     36          CASE ( 0 )
     37             IF ( myid == 0 )  THEN
     38                PRINT*, '+++ local_stop:'
     39                PRINT*, '    local model "', TRIM( coupling_mode ), &
     40                     '" stops now'
     41             ENDIF
     42!
     43!--          Inform the remote model of the termination and its reason, provided
     44!--          the remote model has not already been informed of another
     45!--          termination reason (terminate_coupled > 0) before.
     46             IF ( terminate_coupled == 0 )  THEN
     47                terminate_coupled = 1
     48                CALL MPI_SENDRECV( &
     49                     terminate_coupled,        1, MPI_INTEGER, myid,  0, &
     50                     terminate_coupled_remote, 1, MPI_INTEGER, myid,  0, &
     51                     comm_inter, status, ierr )
     52             ENDIF
     53             CALL MPI_FINALIZE( ierr )
     54
     55          CASE ( 1 )
     56             IF ( myid == 0 )  THEN
     57                PRINT*, '+++ local_stop:'
     58                PRINT*, '    remote model "', TRIM( coupling_mode_remote ), &
     59                     '" stopped'
     60             ENDIF
     61             CALL MPI_FINALIZE( ierr )
     62
     63          CASE ( 2 )
     64             IF ( myid == 0 )  THEN
     65                PRINT*, '+++ local_stop:'
     66                PRINT*, '    remote model "', TRIM( coupling_mode_remote ), &
     67                     '" terminated'
     68                PRINT*, '    with stop_dt = .T.'
     69             ENDIF
     70             stop_dt = .TRUE.
     71
     72          CASE ( 3 )
     73             IF ( myid == 0 )  THEN
     74                PRINT*, '+++ local_stop:'
     75                PRINT*, '    remote model "', TRIM( coupling_mode_remote ), &
     76                     '" terminated'
     77                PRINT*, '    with terminate_run = .T. (CPU-time limit)'
     78             ENDIF
     79             terminate_run = .TRUE.
     80
     81          CASE ( 4 )
     82             IF ( myid == 0 )  THEN
     83                PRINT*, '+++ local_stop:'
     84                PRINT*, '    remote model "', TRIM( coupling_mode_remote ), &
     85                     '" terminated'
     86                PRINT*, '    with terminate_run = .T. (restart)'
     87             ENDIF
     88             terminate_run = .TRUE.
     89             time_restart = time_restart + dt_restart
     90
     91          CASE ( 5 )
     92             IF ( myid == 0 )  THEN
     93                PRINT*, '+++ local_stop:'
     94                PRINT*, '    remote model "', TRIM( coupling_mode_remote ), &
     95                     '" terminated'
     96                PRINT*, '    with terminate_run = .T. (single restart)'
     97             ENDIF
     98             terminate_run = .TRUE.
     99             time_restart = 9999999.9
     100
     101       END SELECT
     102
     103    ENDIF
     104
     105#else
    30106
    31107    STOP
    32108
     109#endif
     110
    33111 END SUBROUTINE local_stop   
Note: See TracChangeset for help on using the changeset viewer.