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/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
Note: See TracChangeset for help on using the changeset viewer.