Ignore:
Timestamp:
Apr 16, 2009 12:07:26 PM (15 years ago)
Author:
raasch
Message:

changes for coupling with independent precursor runs; z_i calculation with Sullivan criterion

File:
1 edited

Legend:

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

    r226 r291  
    44! Actual revisions:
    55! -----------------
    6 !
     6! Coupling with independent precursor runs.
    77!
    88! Former revisions:
     
    2727!-- Local variables
    2828    INTEGER               ::  i, inter_color
    29     INTEGER, DIMENSION(:) ::  bc_data(0:2) = 0
     29    INTEGER, DIMENSION(:) ::  bc_data(0:3) = 0
    3030
    3131!
     
    4848       READ (*,*,ERR=10,END=10)  coupling_mode, bc_data(1), bc_data(2)
    494910     CONTINUE
    50 
    5150#if defined( __mpi2 )
    5251       IF ( TRIM( coupling_mode ) == 'atmosphere_to_ocean' )  THEN
     
    6463       ENDIF
    6564#endif
    66     bc_data(0) = i
     65       bc_data(0) = i
     66
     67!
     68!--    Check if '_O' has to be used as file extension in an uncoupled ocean
     69!--    run. This is required, if this run shall be continued as a coupled run.
     70       IF ( TRIM( coupling_mode ) == 'precursor_ocean' )  bc_data(3) = 1
     71
    6772    ENDIF
    6873
    69     CALL MPI_BCAST( bc_data(0), 3, MPI_INTEGER, 0, MPI_COMM_WORLD, ierr )
     74    CALL MPI_BCAST( bc_data(0), 4, MPI_INTEGER, 0, MPI_COMM_WORLD, ierr )
    7075    i = bc_data(0)
    7176
     
    114119#endif
    115120
    116     IF ( coupling_mode == 'ocean_to_atmosphere' )  coupling_char = '_O'
     121!
     122!-- In case of a precursor ocean run (followed by a coupled run), or a
     123!-- coupled atmosphere-ocean run, set the file extension for the ocean files
     124    IF ( TRIM( coupling_mode ) == 'ocean_to_atmosphere' .OR. bc_data(3) == 1 ) &
     125    THEN
     126       coupling_char = '_O'
     127    ENDIF
    117128
    118129 END SUBROUTINE init_coupling
Note: See TracChangeset for help on using the changeset viewer.