Ignore:
Timestamp:
Oct 7, 2020 1:25:11 PM (4 years ago)
Author:
schwenkel
Message:

Move exchange_horiz from time_integration to modules

File:
1 edited

Legend:

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

    r4627 r4731  
    2424! -----------------
    2525! $Id$
     26! Move exchange_horiz from time_integration to modules
     27!
     28! 4627 2020-07-26 10:14:44Z raasch
    2629! bugfix for r4626
    2730!
     
    6770    USE arrays_3d,                                                                                 &
    6871        ONLY:  c_u, c_u_m, c_u_m_l, c_v, c_v_m, c_v_m_l, c_w, c_w_m, c_w_m_l,                      &
     72               diss,                                                                               &
     73               diss_p,                                                                             &
    6974               dzu,                                                                                &
     75               e,                                                                                  &
     76               e_p,                                                                                &
    7077               exner,                                                                              &
    7178               hyp,                                                                                &
     
    94101               child_domain,                                                                       &
    95102               coupling_mode,                                                                      &
     103               constant_diffusion,                                                                 &
    96104               dt_3d,                                                                              &
    97105               humidity,                                                                           &
     
    113121               passive_scalar,                                                                     &
    114122               restart_string,                                                                     &
     123               rans_mode,                                                                          &
     124               rans_tke_e,                                                                         &
    115125               tsc,                                                                                &
    116126               use_cmax
     127
     128    USE exchange_horiz_mod,                                                                        &
     129        ONLY:  exchange_horiz
     130
    117131
    118132    USE grid_variables,                                                                            &
     
    764778!> Perform module-specific horizontal boundary exchange
    765779!--------------------------------------------------------------------------------------------------!
    766  SUBROUTINE dynamics_exchange_horiz
    767 
    768 
     780 SUBROUTINE dynamics_exchange_horiz( location )
     781
     782       CHARACTER (LEN=*), INTENT(IN) ::  location !< call location string
     783
     784       SELECT CASE ( location )
     785
     786          CASE ( 'before_prognostic_equation' )
     787
     788          CASE ( 'after_prognostic_equation' )
     789
     790             CALL exchange_horiz( u_p, nbgp )
     791             CALL exchange_horiz( v_p, nbgp )
     792             CALL exchange_horiz( w_p, nbgp )
     793             CALL exchange_horiz( pt_p, nbgp )
     794             IF ( .NOT. constant_diffusion )  CALL exchange_horiz( e_p, nbgp )
     795             IF ( rans_tke_e  )               CALL exchange_horiz( diss_p, nbgp )
     796             IF ( humidity )                  CALL exchange_horiz( q_p, nbgp )
     797             IF ( passive_scalar )            CALL exchange_horiz( s_p, nbgp )
     798
     799          CASE ( 'after_anterpolation' )
     800
     801             CALL exchange_horiz( u, nbgp )
     802             CALL exchange_horiz( v, nbgp )
     803             CALL exchange_horiz( w, nbgp )
     804             IF ( .NOT. neutral )             CALL exchange_horiz( pt, nbgp )
     805             IF ( humidity )                  CALL exchange_horiz( q, nbgp )
     806             IF ( passive_scalar )            CALL exchange_horiz( s, nbgp )
     807             IF ( .NOT. constant_diffusion )  CALL exchange_horiz( e, nbgp )
     808             IF ( .NOT. constant_diffusion  .AND.  rans_mode  .AND.  rans_tke_e )  THEN
     809                CALL exchange_horiz( diss, nbgp )
     810             ENDIF
     811
     812       END SELECT
    769813
    770814 END SUBROUTINE dynamics_exchange_horiz
Note: See TracChangeset for help on using the changeset viewer.