Changeset 4731


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

Move exchange_horiz from time_integration to modules

Location:
palm/trunk/SOURCE
Files:
9 edited

Legend:

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

    r4671 r4731  
    2424! -----------------
    2525! $Id$
     26! Move exchange_horiz from time_integration to modules
     27!
     28! 4671 2020-09-09 20:27:58Z pavelkrc
    2629! Implementation of downward facing USM and LSM surfaces
    2730!
     
    14701473! Description:
    14711474! ------------
    1472 !> Control of microphysics for all grid points
    1473 !--------------------------------------------------------------------------------------------------!
    1474     SUBROUTINE bcm_exchange_horiz
     1475!> Exchange ghostpoints
     1476!--------------------------------------------------------------------------------------------------!
     1477    SUBROUTINE bcm_exchange_horiz( location )
    14751478
    14761479       USE exchange_horiz_mod,                                                                     &
    14771480           ONLY:  exchange_horiz
    14781481
    1479 
    1480        IF ( .NOT. microphysics_sat_adjust  .AND.  ( intermediate_timestep_count == 1  .OR.         &
    1481             call_microphysics_at_all_substeps ) )                                                  &
    1482        THEN
    1483           IF ( microphysics_morrison )  THEN
    1484              CALL exchange_horiz( nc, nbgp )
    1485              CALL exchange_horiz( qc, nbgp )
    1486           ENDIF
    1487           IF ( microphysics_seifert ) THEN
    1488              CALL exchange_horiz( qr, nbgp )
    1489              CALL exchange_horiz( nr, nbgp )
    1490           ENDIF
    1491           IF ( microphysics_ice_phase ) THEN
    1492              CALL exchange_horiz( qi, nbgp )
    1493              CALL exchange_horiz( ni, nbgp )
    1494           ENDIF
    1495           CALL exchange_horiz( q, nbgp )
    1496           CALL exchange_horiz( pt, nbgp )
    1497        ENDIF
    1498 
     1482       CHARACTER (LEN=*), INTENT(IN) ::  location !< call location string
     1483
     1484       SELECT CASE ( location )
     1485
     1486          CASE ( 'before_prognostic_equation' )
     1487
     1488             IF ( .NOT. microphysics_sat_adjust  .AND.  ( intermediate_timestep_count == 1  .OR.   &
     1489                  call_microphysics_at_all_substeps ) )                                            &
     1490             THEN
     1491                IF ( microphysics_morrison )  THEN
     1492                   CALL exchange_horiz( nc, nbgp )
     1493                   CALL exchange_horiz( qc, nbgp )
     1494                ENDIF
     1495                IF ( microphysics_seifert ) THEN
     1496                   CALL exchange_horiz( qr, nbgp )
     1497                   CALL exchange_horiz( nr, nbgp )
     1498                ENDIF
     1499                IF ( microphysics_ice_phase ) THEN
     1500                   CALL exchange_horiz( qi, nbgp )
     1501                   CALL exchange_horiz( ni, nbgp )
     1502                ENDIF
     1503                CALL exchange_horiz( q, nbgp )
     1504                CALL exchange_horiz( pt, nbgp )
     1505             ENDIF
     1506
     1507          CASE ( 'after_prognostic_equation' )
     1508
     1509             IF ( collision_turbulence )  THEN
     1510                CALL exchange_horiz( diss, nbgp )
     1511             ENDIF
     1512             IF ( microphysics_morrison )  THEN
     1513                CALL exchange_horiz( qc_p, nbgp )
     1514                CALL exchange_horiz( nc_p, nbgp )
     1515             ENDIF
     1516             IF ( microphysics_seifert )  THEN
     1517                CALL exchange_horiz( qr_p, nbgp )
     1518                CALL exchange_horiz( nr_p, nbgp )
     1519             ENDIF
     1520             IF ( microphysics_ice_phase )  THEN
     1521                CALL exchange_horiz( qi_p, nbgp )
     1522                CALL exchange_horiz( ni_p, nbgp )
     1523             ENDIF
     1524
     1525          CASE ( 'after_anterpolation' )
     1526
     1527             IF ( microphysics_morrison )  THEN
     1528                CALL exchange_horiz( qc, nbgp )
     1529                CALL exchange_horiz( nc, nbgp )
     1530             ENDIF
     1531             IF ( microphysics_seifert )  THEN
     1532                CALL exchange_horiz( qr, nbgp )
     1533                CALL exchange_horiz( nr, nbgp )
     1534             ENDIF
     1535             IF ( microphysics_ice_phase )  THEN
     1536                CALL exchange_horiz( qi, nbgp )
     1537                CALL exchange_horiz( ni, nbgp )
     1538             ENDIF
     1539
     1540       END SELECT
    14991541
    15001542    END SUBROUTINE bcm_exchange_horiz
    1501 
    15021543
    15031544
  • palm/trunk/SOURCE/chemistry_model_mod.f90

    r4671 r4731  
    2626! -----------------
    2727! $Id$
     28! Move exchange_horiz from time_integration to modules
     29!
     30! 4671 2020-09-09 20:27:58Z pavelkrc
    2831! Implementation of downward facing USM and LSM surfaces
    2932!
     
    29342937!> routine for exchange horiz of chemical quantities
    29352938!--------------------------------------------------------------------------------------------------!
    2936  SUBROUTINE chem_exchange_horiz_bounds
     2939 SUBROUTINE chem_exchange_horiz_bounds( location )
    29372940
    29382941    USE exchange_horiz_mod,                                                                        &
     
    29402943
    29412944   INTEGER(iwp) ::  lsp       !<
    2942 
    2943 !
    2944 !--    Loop over chemical species
    2945        CALL cpu_log( log_point_s(84), 'chem.exch-horiz', 'start' )
    2946        DO  lsp = 1, nvar
    2947           CALL exchange_horiz( chem_species(lsp)%conc, nbgp,                                       &
    2948                                alternative_communicator = communicator_chem )
    2949        ENDDO
    2950 
    2951        CALL chem_boundary_conditions( horizontal_conditions_only = .TRUE. )
    2952 
    2953        CALL cpu_log( log_point_s(84), 'chem.exch-horiz', 'stop' )
    2954 
     2945   INTEGER(iwp) ::  n
     2946
     2947   CHARACTER (LEN=*), INTENT(IN) ::  location !< call location string
     2948
     2949   SELECT CASE ( location )
     2950
     2951       CASE ( 'before_prognostic_equation' )
     2952!
     2953!--       Loop over chemical species
     2954          CALL cpu_log( log_point_s(84), 'chem.exch-horiz', 'start' )
     2955          DO  lsp = 1, nvar
     2956             CALL exchange_horiz( chem_species(lsp)%conc, nbgp,                                    &
     2957                                  alternative_communicator = communicator_chem )
     2958          ENDDO
     2959
     2960          CALL chem_boundary_conditions( horizontal_conditions_only = .TRUE. )
     2961
     2962          CALL cpu_log( log_point_s(84), 'chem.exch-horiz', 'stop' )
     2963
     2964       CASE ( 'after_prognostic_equation' )
     2965
     2966          IF ( air_chemistry )  THEN
     2967             DO  n = 1, nvar
     2968                CALL exchange_horiz( chem_species(n)%conc_p, nbgp,                                 &
     2969                                     alternative_communicator = communicator_chem )
     2970             ENDDO
     2971          ENDIF
     2972
     2973       CASE ( 'after_anterpolation' )
     2974
     2975          IF ( air_chemistry )  THEN
     2976             DO  n = 1, nvar
     2977                CALL exchange_horiz( chem_species(n)%conc, nbgp,                                   &
     2978                                     alternative_communicator = communicator_chem )
     2979             ENDDO
     2980          ENDIF
     2981
     2982    END SELECT
    29552983
    29562984 END SUBROUTINE chem_exchange_horiz_bounds
  • 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
  • palm/trunk/SOURCE/lagrangian_particle_model_mod.f90

    r4673 r4731  
    2424! -----------------
    2525! $Id$
     26! Move exchange_horiz from time_integration to modules
     27!
     28! 4673 2020-09-10 07:56:36Z schwenkel
    2629! bugfix in case of mpi-restarts
    2730!
     
    413416           lpm_actions,                                                                            &
    414417           lpm_data_output_ptseries,                                                               &
     418           lpm_exchange_horiz_bounds,                                                              &
    415419           lpm_interaction_droplets_ptq,                                                           &
    416420           lpm_rrd_local_particles,                                                                &
     
    513517       MODULE PROCEDURE lpm_exchange_horiz
    514518    END INTERFACE lpm_exchange_horiz
     519
     520    INTERFACE lpm_exchange_horiz_bounds
     521       MODULE PROCEDURE lpm_exchange_horiz_bounds
     522    END INTERFACE lpm_exchange_horiz_bounds
    515523
    516524    INTERFACE lpm_move_particle
     
    77647772 END SUBROUTINE lpm_exchange_horiz
    77657773
     7774
     7775!--------------------------------------------------------------------------------------------------!
     7776! Description:
     7777! ------------
     7778!> Exchange ghostpoints
     7779!--------------------------------------------------------------------------------------------------!
     7780    SUBROUTINE lpm_exchange_horiz_bounds( location )
     7781
     7782    USE exchange_horiz_mod,                                                                        &
     7783        ONLY:  exchange_horiz
     7784
     7785       CHARACTER (LEN=*), INTENT(IN) ::  location !< call location string
     7786
     7787       SELECT CASE ( location )
     7788
     7789          CASE ( 'before_prognostic_equation' )
     7790
     7791          CASE ( 'after_prognostic_equation' )
     7792
     7793             IF ( wang_kernel  .OR.  use_sgs_for_particles )  THEN
     7794                CALL exchange_horiz( diss, nbgp )
     7795             ENDIF
     7796
     7797       END SELECT
     7798
     7799    END SUBROUTINE lpm_exchange_horiz_bounds
     7800
     7801
    77667802#if defined( __parallel )
    77677803!--------------------------------------------------------------------------------------------------!
  • palm/trunk/SOURCE/module_interface.f90

    r4708 r4731  
    2525! -----------------
    2626! $Id$
     27! Move exchange_horiz from time_integration to modules
     28!
     29! 4708 2020-09-28 17:42:58Z suehring
    2730! pass fillvalue attribute to radiation output
    2831!
     
    390393               lpm_header,                                                     &
    391394               lpm_check_parameters,                                           &
     395               lpm_exchange_horiz_bounds,                                      &
    392396               lpm_init_arrays,                                                &
    393397               lpm_init,                                                       &
     
    432436               ocean_check_data_output_pr,                                     &
    433437               ocean_check_data_output,                                        &
     438               ocean_exchange_horiz,                                           &
    434439               ocean_init_arrays,                                              &
    435440               ocean_init,                                                     &
     
    13501355!> Exchange horiz for module-specific quantities
    13511356!------------------------------------------------------------------------------!
    1352  SUBROUTINE module_interface_exchange_horiz
    1353 
     1357 SUBROUTINE module_interface_exchange_horiz( location )
     1358
     1359    CHARACTER (LEN=*), INTENT(IN) ::  location !< call location string
    13541360
    13551361    IF ( debug_output_timestep )  CALL debug_message( 'module-specific exchange_horiz', 'start' )
    13561362
    1357     CALL dynamics_exchange_horiz
    1358 
    1359     IF ( bulk_cloud_model    )  CALL bcm_exchange_horiz
    1360     IF ( air_chemistry       )  CALL chem_exchange_horiz_bounds
    1361     IF ( salsa               )  CALL salsa_exchange_horiz_bounds
     1363    CALL dynamics_exchange_horiz( location )
     1364
     1365    IF ( bulk_cloud_model    )  CALL bcm_exchange_horiz( location )
     1366    IF ( air_chemistry       )  CALL chem_exchange_horiz_bounds( location )
     1367    IF ( ocean_mode          )  CALL ocean_exchange_horiz( location )
     1368    IF ( particle_advection  )  CALL lpm_exchange_horiz_bounds ( location )
     1369    IF ( salsa               )  CALL salsa_exchange_horiz_bounds( location )
    13621370
    13631371    IF ( debug_output_timestep )  CALL debug_message( 'module-specific exchange_horiz', 'end' )
  • palm/trunk/SOURCE/ocean_mod.f90

    r4671 r4731  
    2525! -----------------
    2626! $Id$
     27! Move exchange_horiz from time_integration to modules
     28!
     29! 4671 2020-09-09 20:27:58Z pavelkrc
    2730! Implementation of downward facing USM and LSM surfaces
    2831!
     
    9699    USE control_parameters,                                                    &
    97100        ONLY:  atmos_ocean_sign, bottom_salinityflux,                          &
    98                constant_top_salinityflux, restart_data_format_output, ocean_mode, top_salinityflux, &
     101               constant_top_salinityflux, restart_data_format_output, ocean_mode, top_salinityflux,&
    99102               wall_salinityflux, loop_optimization, ws_scheme_sca
    100103
     
    108111
    109112    USE indices,                                                               &
    110         ONLY:  advc_flags_s, nxl, nxr, nyn, nys, nzb, nzt, wall_flags_total_0
     113        ONLY:  advc_flags_s, nxl, nxr, nyn, nys, nzb, nzt, wall_flags_total_0, nbgp
    111114
    112115    USE restart_data_mpi_io_mod,                                                                   &
     
    117120        ONLY:  bc_h, surf_def_v, surf_def_h, surf_lsm_h, surf_lsm_v,           &
    118121               surf_usm_h, surf_usm_v
     122
     123       USE exchange_horiz_mod,                                                                     &
     124           ONLY:  exchange_horiz
     125
    119126
    120127    IMPLICIT NONE
     
    202209    END INTERFACE ocean_data_output_3d
    203210
     211    INTERFACE ocean_exchange_horiz
     212       MODULE PROCEDURE ocean_exchange_horiz
     213    END INTERFACE ocean_exchange_horiz
     214
    204215    INTERFACE ocean_header
    205216       MODULE PROCEDURE ocean_header
     
    273284    PUBLIC eqn_state_seawater, ocean_actions, ocean_check_data_output,         &
    274285           ocean_check_data_output_pr, ocean_check_parameters,                 &
    275            ocean_data_output_2d, ocean_data_output_3d,                         &
     286           ocean_data_output_2d, ocean_data_output_3d, ocean_exchange_horiz,   &
    276287           ocean_define_netcdf_grid, ocean_header, ocean_init,                 &
    277288           ocean_init_arrays, ocean_parin, ocean_prognostic_equations,         &
     
    11651176
    11661177 END SUBROUTINE ocean_data_output_3d
     1178
     1179
     1180!--------------------------------------------------------------------------------------------------!
     1181! Description:
     1182! ------------
     1183!> Exchange ghostpoints
     1184!--------------------------------------------------------------------------------------------------!
     1185    SUBROUTINE ocean_exchange_horiz( location )
     1186
     1187       CHARACTER (LEN=*), INTENT(IN) ::  location !< call location string
     1188
     1189       SELECT CASE ( location )
     1190
     1191          CASE ( 'before_prognostic_equation' )
     1192
     1193          CASE ( 'after_prognostic_equation' )
     1194
     1195             CALL exchange_horiz( sa_p, nbgp )
     1196             CALL exchange_horiz( rho_ocean, nbgp )
     1197             CALL exchange_horiz( prho, nbgp )
     1198
     1199       END SELECT
     1200
     1201    END SUBROUTINE ocean_exchange_horiz
     1202
    11671203
    11681204
  • palm/trunk/SOURCE/prognostic_equations.f90

    r4717 r4731  
    2525! -----------------
    2626! $Id$
     27! Move exchange_horiz from time_integration to modules
     28!
     29! 4717 2020-09-30 22:27:40Z pavelkrc
    2730! Fixes and optimizations of OpenMP parallelization, formatting of OpenMP
    2831! directives (J. Resler)
     
    411414!-- Module Inferface for exchange horiz after non_advective_processes but before advection.
    412415!-- Therefore, non_advective_processes must not run for ghost points.
    413     CALL module_interface_exchange_horiz()
     416    CALL module_interface_exchange_horiz( 'before_prognostic_equation' )
    414417!
    415418!-- Loop over all prognostic equations
     
    917920!-- Module Inferface for exchange horiz after non_advective_processes but before advection.
    918921!-- Therefore, non_advective_processes must not run for ghost points.
    919     CALL module_interface_exchange_horiz()
     922    CALL module_interface_exchange_horiz( 'before_prognostic_equation' )
    920923!
    921924!-- u-velocity component
  • palm/trunk/SOURCE/salsa_mod.f90

    r4671 r4731  
    2626! -----------------
    2727! $Id$
     28! Move exchange_horiz from time_integration to modules
     29!
     30! 4671 2020-09-09 20:27:58Z pavelkrc
    2831! Implementation of downward facing USM and LSM surfaces
    2932!
     
    83328335!> Routine for exchange horiz of salsa variables.
    83338336!------------------------------------------------------------------------------!
    8334  SUBROUTINE salsa_exchange_horiz_bounds
     8337 SUBROUTINE salsa_exchange_horiz_bounds ( location )
    83358338
    83368339    USE cpulog,                                                                &
     
    83478350    INTEGER(iwp) ::  ig   !<
    83488351
    8349     IF ( time_since_reference_point >= skip_time_do_salsa )  THEN
    8350        IF ( ( time_since_reference_point - last_salsa_time ) >= dt_salsa )  THEN
    8351 
    8352           CALL cpu_log( log_point_s(91), 'salsa exch-horiz ', 'start' )
    8353 !
    8354 !--       Exchange ghost points
    8355           DO  ib = 1, nbins_aerosol
    8356              CALL exchange_horiz( aerosol_number(ib)%conc, nbgp,                                   &
    8357                                   alternative_communicator = communicator_salsa )
    8358              DO  ic = 1, ncomponents_mass
    8359                 icc = ( ic - 1 ) * nbins_aerosol + ib
    8360                 CALL exchange_horiz( aerosol_mass(icc)%conc, nbgp,                                 &
     8352    CHARACTER (LEN=*), INTENT(IN) ::  location !< call location string
     8353
     8354    SELECT CASE ( location )
     8355
     8356       CASE ( 'before_prognostic_equation' )
     8357
     8358          IF ( time_since_reference_point >= skip_time_do_salsa )  THEN
     8359             IF ( ( time_since_reference_point - last_salsa_time ) >= dt_salsa )  THEN
     8360
     8361                CALL cpu_log( log_point_s(91), 'salsa exch-horiz ', 'start' )
     8362!
     8363!--             Exchange ghost points
     8364                DO  ib = 1, nbins_aerosol
     8365                   CALL exchange_horiz( aerosol_number(ib)%conc, nbgp,                             &
     8366                                        alternative_communicator = communicator_salsa )
     8367                   DO  ic = 1, ncomponents_mass
     8368                      icc = ( ic - 1 ) * nbins_aerosol + ib
     8369                      CALL exchange_horiz( aerosol_mass(icc)%conc, nbgp,                           &
     8370                                           alternative_communicator = communicator_salsa )
     8371                   ENDDO
     8372                ENDDO
     8373                IF ( .NOT. salsa_gases_from_chem )  THEN
     8374                   DO  ig = 1, ngases_salsa
     8375                      CALL exchange_horiz( salsa_gas(ig)%conc, nbgp,                               &
     8376                                           alternative_communicator = communicator_salsa )
     8377                   ENDDO
     8378                ENDIF
     8379!
     8380!--             Apply only horizontal boundary conditions
     8381                CALL salsa_boundary_conditions( horizontal_conditions_only = .TRUE. )
     8382                CALL cpu_log( log_point_s(91), 'salsa exch-horiz ', 'stop' )
     8383!
     8384!--             Update last_salsa_time
     8385                last_salsa_time = time_since_reference_point
     8386             ENDIF
     8387          ENDIF
     8388
     8389       CASE ( 'after_prognostic_equation' )
     8390
     8391          IF ( salsa  .AND.  time_since_reference_point >= skip_time_do_salsa )  THEN
     8392             DO  ib = 1, nbins_aerosol
     8393                CALL exchange_horiz( aerosol_number(ib)%conc_p, nbgp,                              &
    83618394                                     alternative_communicator = communicator_salsa )
     8395                DO  ic = 1, ncomponents_mass
     8396                   icc = ( ic - 1 ) * nbins_aerosol + ib
     8397                   CALL exchange_horiz( aerosol_mass(icc)%conc_p, nbgp,                            &
     8398                                        alternative_communicator = communicator_salsa )
     8399                ENDDO
    83628400             ENDDO
    8363           ENDDO
    8364           IF ( .NOT. salsa_gases_from_chem )  THEN
    8365              DO  ig = 1, ngases_salsa
    8366                 CALL exchange_horiz( salsa_gas(ig)%conc, nbgp,                                     &
     8401             IF ( .NOT. salsa_gases_from_chem )  THEN
     8402                DO  ig = 1, ngases_salsa
     8403                   CALL exchange_horiz( salsa_gas(ig)%conc_p, nbgp,                                &
     8404                                        alternative_communicator = communicator_salsa )
     8405                ENDDO
     8406             ENDIF
     8407          ENDIF
     8408
     8409       CASE ( 'after_anterpolation' )
     8410
     8411          IF ( salsa  .AND. time_since_reference_point >= skip_time_do_salsa )  THEN
     8412             DO  ib = 1, nbins_aerosol
     8413                CALL exchange_horiz( aerosol_number(ib)%conc, nbgp,                                &
    83678414                                     alternative_communicator = communicator_salsa )
     8415                DO  ic = 1, ncomponents_mass
     8416                   icc = ( ic - 1 ) * nbins_aerosol + ib
     8417                   CALL exchange_horiz( aerosol_mass(icc)%conc, nbgp,                              &
     8418                                        alternative_communicator = communicator_salsa )
     8419                ENDDO
    83688420             ENDDO
     8421             IF ( .NOT. salsa_gases_from_chem )  THEN
     8422                DO  ig = 1, ngases_salsa
     8423                   CALL exchange_horiz( salsa_gas(ig)%conc, nbgp,                                  &
     8424                                        alternative_communicator = communicator_salsa )
     8425                ENDDO
     8426             ENDIF
    83698427          ENDIF
    8370 !
    8371 !--       Apply only horizontal boundary conditions
    8372           CALL salsa_boundary_conditions( horizontal_conditions_only = .TRUE. )
    8373           CALL cpu_log( log_point_s(91), 'salsa exch-horiz ', 'stop' )
    8374 !
    8375 !--       Update last_salsa_time
    8376           last_salsa_time = time_since_reference_point
    8377        ENDIF
    8378     ENDIF
     8428
     8429    END SELECT
    83798430
    83808431 END SUBROUTINE salsa_exchange_horiz_bounds
     8432
    83818433
    83828434!------------------------------------------------------------------------------!
  • palm/trunk/SOURCE/time_integration.f90

    r4671 r4731  
    2525! -----------------
    2626! $Id$
     27! Move exchange_horiz from time_integration to modules
     28!
     29! 4671 2020-09-09 20:27:58Z pavelkrc
    2730! Implementation of downward facing USM and LSM surfaces
    2831!
     
    252255
    253256    USE arrays_3d,                                                                                 &
    254         ONLY:  diss, diss_p, dzu, e_p, nc_p, ni_p, nr_p, prho, pt, pt_p, pt_init, q, qc_p, qr_p,   &
    255                q_init, q_p, qi_p, ref_state, rho_ocean, sa_p, s_p, tend, u, u_p, v, vpt, v_p, w_p
    256 
    257 #if defined( __parallel )  &&  ! defined( _OPENACC )
    258     USE arrays_3d,                                                                                 &
    259         ONLY:  e, nc, ni, nr, qc, qi, qr, s, w
    260 #endif
     257        ONLY:  dzu, prho, pt, pt_init, q,                                                          &
     258               q_init, ref_state, rho_ocean, tend, u, v, vpt
    261259
    262260    USE biometeorology_mod,                                                                        &
     
    265263
    266264    USE bulk_cloud_model_mod,                                                                      &
    267         ONLY: bulk_cloud_model, calc_liquid_water_content, collision_turbulence,                   &
    268               microphysics_ice_phase, microphysics_morrison, microphysics_seifert
     265        ONLY: bulk_cloud_model, calc_liquid_water_content
    269266
    270267    USE calc_mean_profile_mod,                                                                     &
     
    278275
    279276    USE chem_modules,                                                                              &
    280         ONLY:  bc_cs_t_val, chem_species, communicator_chem, emissions_anthropogenic,              &
     277        ONLY:  bc_cs_t_val, chem_species, emissions_anthropogenic,                                 &
    281278               emiss_read_legacy_mode, n_matched_vars
    282279
     
    296293               land_surface, large_scale_forcing, loop_optimization, lsf_surf, lsf_vert, masks,    &
    297294               multi_agent_system_end, multi_agent_system_start, nesting_offline, neutral,         &
    298                nr_timesteps_this_run, nudging, ocean_mode, passive_scalar, pt_reference,           &
     295               nr_timesteps_this_run, nudging, ocean_mode, pt_reference,                           &
    299296               pt_slope_offset, pt_surface_heating_rate,                                           &
    300                random_heatflux, rans_tke_e, run_coupled, salsa,                                    &
     297               random_heatflux, run_coupled, salsa,                                                &
    301298               simulated_time, simulated_time_chr, skip_time_do2d_xy, skip_time_do2d_xz,           &
    302299               skip_time_do2d_yz, skip_time_do3d, skip_time_domask, skip_time_dopr,                &
     
    310307               virtual_flight, virtual_measurement, ws_scheme_mom, ws_scheme_sca
    311308
    312 #if defined( __parallel )
    313     USE control_parameters,                                                                        &
    314         ONLY:  rans_mode
    315 #endif
    316 
    317309    USE cpulog,                                                                                    &
    318310        ONLY:  cpu_log, log_point, log_point_s
     
    332324
    333325    USE indices,                                                                                   &
    334         ONLY:  nbgp, nx, nxl, nxlg, nxr, nxrg, nzb, nzt
     326        ONLY:  nx, nxl, nxlg, nxr, nxrg, nzb, nzt
    335327
    336328    USE indoor_model_mod,                                                                          &
     
    352344    USE module_interface,                                                                          &
    353345        ONLY:  module_interface_actions, module_interface_swap_timelevel,                          &
    354                module_interface_boundary_conditions
     346               module_interface_boundary_conditions, module_interface_exchange_horiz
    355347
    356348    USE multi_agent_system_mod,                                                                    &
     
    373365
    374366    USE particle_attributes,                                                                       &
    375         ONLY:  particle_advection, particle_advection_start, use_sgs_for_particles, wang_kernel
     367        ONLY:  particle_advection, particle_advection_start
    376368
    377369    USE pegrid
     
    396388    USE salsa_mod,                                                                                 &
    397389        ONLY: aerosol_number, aerosol_mass, bc_am_t_val, bc_an_t_val, bc_gt_t_val,                 &
    398               communicator_salsa, nbins_aerosol, ncomponents_mass, ngases_salsa,                   &
     390              nbins_aerosol, ncomponents_mass, ngases_salsa,                                       &
    399391              salsa_boundary_conditions, salsa_emission_update, salsa_gas, salsa_gases_from_chem,  &
    400392              skip_time_do_salsa
     
    769761          ENDIF
    770762!
    771 !--       Execute all other module actions routunes
     763!--       Execute all other module actions routines
    772764          CALL module_interface_actions( 'before_prognostic_equations' )
    773765!
     
    797789          CALL cpu_log( log_point(26), 'exchange-horiz-progn', 'start' )
    798790
    799           CALL exchange_horiz( u_p, nbgp )
    800           CALL exchange_horiz( v_p, nbgp )
    801           CALL exchange_horiz( w_p, nbgp )
    802           CALL exchange_horiz( pt_p, nbgp )
    803           IF ( .NOT. constant_diffusion )  CALL exchange_horiz( e_p, nbgp )
    804           IF ( rans_tke_e  .OR.  wang_kernel  .OR.  collision_turbulence                           &
    805                .OR.  use_sgs_for_particles )  THEN
    806              IF ( rans_tke_e )  THEN
    807                 CALL exchange_horiz( diss_p, nbgp )
    808              ELSE
    809                 CALL exchange_horiz( diss, nbgp )
    810              ENDIF
    811           ENDIF
    812           IF ( ocean_mode )  THEN
    813              CALL exchange_horiz( sa_p, nbgp )
    814              CALL exchange_horiz( rho_ocean, nbgp )
    815              CALL exchange_horiz( prho, nbgp )
    816           ENDIF
    817           IF ( humidity )  THEN
    818              CALL exchange_horiz( q_p, nbgp )
    819              IF ( bulk_cloud_model .AND. microphysics_morrison )  THEN
    820                 CALL exchange_horiz( qc_p, nbgp )
    821                 CALL exchange_horiz( nc_p, nbgp )
    822              ENDIF
    823              IF ( bulk_cloud_model .AND. microphysics_seifert )  THEN
    824                 CALL exchange_horiz( qr_p, nbgp )
    825                 CALL exchange_horiz( nr_p, nbgp )
    826              ENDIF
    827              IF ( bulk_cloud_model .AND. microphysics_ice_phase )  THEN
    828                 CALL exchange_horiz( qi_p, nbgp )
    829                 CALL exchange_horiz( ni_p, nbgp )
    830              ENDIF
    831           ENDIF
    832           IF ( passive_scalar )  CALL exchange_horiz( s_p, nbgp )
    833           IF ( air_chemistry )  THEN
    834              DO  n = 1, nvar
    835                 CALL exchange_horiz( chem_species(n)%conc_p, nbgp,                                 &
    836                                      alternative_communicator = communicator_chem )
    837              ENDDO
    838           ENDIF
    839 
    840           IF ( salsa  .AND.  time_since_reference_point >= skip_time_do_salsa )  THEN
    841              DO  ib = 1, nbins_aerosol
    842                 CALL exchange_horiz( aerosol_number(ib)%conc_p, nbgp,                              &
    843                                      alternative_communicator = communicator_salsa )
    844                 DO  ic = 1, ncomponents_mass
    845                    icc = ( ic - 1 ) * nbins_aerosol + ib
    846                    CALL exchange_horiz( aerosol_mass(icc)%conc_p, nbgp,                            &
    847                                         alternative_communicator = communicator_salsa )
    848                 ENDDO
    849              ENDDO
    850              IF ( .NOT. salsa_gases_from_chem )  THEN
    851                 DO  ig = 1, ngases_salsa
    852                    CALL exchange_horiz( salsa_gas(ig)%conc_p, nbgp,                                &
    853                                         alternative_communicator = communicator_salsa )
    854                 ENDDO
    855              ENDIF
    856           ENDIF
     791          CALL module_interface_exchange_horiz( 'after_prognostic_equation' )
    857792
    858793          CALL cpu_log( log_point(26), 'exchange-horiz-progn', 'stop' )
     
    899834!--             Exchange_horiz is needed for all parent-domains after the
    900835!--             anterpolation
    901                 CALL exchange_horiz( u, nbgp )
    902                 CALL exchange_horiz( v, nbgp )
    903                 CALL exchange_horiz( w, nbgp )
    904                 IF ( .NOT. neutral )  CALL exchange_horiz( pt, nbgp )
    905 
    906                 IF ( humidity )  THEN
    907 
    908                    CALL exchange_horiz( q, nbgp )
    909 
    910                    IF ( bulk_cloud_model  .AND.  microphysics_morrison )  THEN
    911                        CALL exchange_horiz( qc, nbgp )
    912                        CALL exchange_horiz( nc, nbgp )
    913                    ENDIF
    914                    IF ( bulk_cloud_model  .AND.  microphysics_seifert )  THEN
    915                        CALL exchange_horiz( qr, nbgp )
    916                        CALL exchange_horiz( nr, nbgp )
    917                    ENDIF
    918                    IF ( bulk_cloud_model  .AND.  microphysics_ice_phase )  THEN
    919                       CALL exchange_horiz( qi, nbgp )
    920                       CALL exchange_horiz( ni, nbgp )
    921                    ENDIF
    922 
    923                 ENDIF
    924 
    925                 IF ( passive_scalar )  CALL exchange_horiz( s, nbgp )
    926 
    927                 IF ( .NOT. constant_diffusion )  CALL exchange_horiz( e, nbgp )
    928 
    929                 IF ( .NOT. constant_diffusion  .AND.  rans_mode  .AND.  rans_tke_e )  THEN
    930                    CALL exchange_horiz( diss, nbgp )
    931                 ENDIF
    932 
    933                 IF ( air_chemistry )  THEN
    934                    DO  n = 1, nvar
    935                       CALL exchange_horiz( chem_species(n)%conc, nbgp,                             &
    936                                            alternative_communicator = communicator_chem )
    937                    ENDDO
    938                 ENDIF
    939 
    940                 IF ( salsa  .AND. time_since_reference_point >= skip_time_do_salsa )  THEN
    941                    DO  ib = 1, nbins_aerosol
    942                       CALL exchange_horiz( aerosol_number(ib)%conc, nbgp,                          &
    943                                            alternative_communicator = communicator_salsa )
    944                       DO  ic = 1, ncomponents_mass
    945                          icc = ( ic - 1 ) * nbins_aerosol + ib
    946                          CALL exchange_horiz( aerosol_mass(icc)%conc, nbgp,                        &
    947                                               alternative_communicator = communicator_salsa )
    948                       ENDDO
    949                    ENDDO
    950                    IF ( .NOT. salsa_gases_from_chem )  THEN
    951                       DO  ig = 1, ngases_salsa
    952                          CALL exchange_horiz( salsa_gas(ig)%conc, nbgp,                            &
    953                                               alternative_communicator = communicator_salsa )
    954                       ENDDO
    955                    ENDIF
    956                 ENDIF
     836                CALL module_interface_exchange_horiz( 'after_anterpolation' )
     837
    957838                CALL cpu_log( log_point_s(92), 'exchange-horiz-nest', 'stop' )
    958839
Note: See TracChangeset for help on using the changeset viewer.