Ignore:
Timestamp:
Jun 12, 2020 2:03:36 PM (4 years ago)
Author:
raasch
Message:

Vertical nesting method of Huq et al. (2019) removed

File:
1 edited

Legend:

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

    r4521 r4564  
    2525! -----------------
    2626! $Id$
     27! Vertical nesting method of Huq et al. (2019) removed
     28!
     29! 4521 2020-05-06 11:39:49Z schwenkel
    2730! Rename variable
    2831!
     
    398401               usm_surface_energy_balance, usm_green_heat_model
    399402
    400     USE vertical_nesting_mod,                                                                      &
    401         ONLY:  vnested, vnest_init
    402 
    403 #if defined( __parallel )
    404     USE vertical_nesting_mod,                                                                      &
    405         ONLY:  vnest_anterpolate, vnest_anterpolate_e, vnest_boundary_conds,                       &
    406                vnest_boundary_conds_khkm, vnest_deallocate, vnest_init_fine, vnest_start_time
    407 #endif
    408 
    409403    USE virtual_measurement_mod,                                                                   &
    410404        ONLY:  dt_virtual_measurement,                                                             &
     
    616610!-- Data exchange between coupled models in case that a call has been omitted
    617611!-- at the end of the previous run of a job chain.
    618     IF ( coupling_mode /= 'uncoupled'  .AND.  run_coupled  .AND. .NOT. vnested )  THEN
     612    IF ( coupling_mode /= 'uncoupled'  .AND.  run_coupled )  THEN
    619613!
    620614!--    In case of model termination initiated by the local model the coupler
     
    636630
    637631       CALL cpu_log( log_point_s(10), 'timesteps', 'start' )
    638 
    639 #if defined( __parallel )
    640 !
    641 !--    Vertical nesting: initialize fine grid
    642        IF ( vnested ) THEN
    643           IF ( .NOT. vnest_init  .AND.  simulated_time >= vnest_start_time )  THEN
    644              CALL cpu_log( log_point_s(22), 'vnest_init', 'start' )
    645              CALL vnest_init_fine
    646              vnest_init = .TRUE.
    647              CALL cpu_log( log_point_s(22), 'vnest_init', 'stop' )
    648           ENDIF
    649        ENDIF
    650 #endif
    651632
    652633!
     
    868849
    869850#if defined( __parallel )
    870 !
    871 !--       Vertical nesting: Interpolate fine grid data to the coarse grid
    872           IF ( vnest_init ) THEN
    873              CALL cpu_log( log_point_s(37), 'vnest_anterpolate', 'start' )
    874              CALL vnest_anterpolate
    875              CALL cpu_log( log_point_s(37), 'vnest_anterpolate', 'stop' )
    876           ENDIF
    877 
    878851          IF ( nested_run )  THEN
    879852
     
    10331006!--       Reduce the velocity divergence via the equation for perturbation
    10341007!--       pressure.
    1035           IF ( intermediate_timestep_count == 1  .OR. &
    1036                 call_psolver_at_all_substeps )  THEN
    1037 
    1038              IF (  vnest_init ) THEN
     1008          IF ( intermediate_timestep_count == 1  .OR.  call_psolver_at_all_substeps )  THEN
     1009
    10391010#if defined( __parallel )
    10401011!
    1041 !--             Compute pressure in the CG, interpolate top boundary conditions
    1042 !--             to the FG and then compute pressure in the FG
    1043                 IF ( coupling_mode == 'vnested_crse' )  CALL pres
    1044 
    1045                 CALL cpu_log( log_point_s(30), 'vnest_bc', 'start' )
    1046                 CALL vnest_boundary_conds
    1047                 CALL cpu_log( log_point_s(30), 'vnest_bc', 'stop' )
    1048 
    1049                 IF ( coupling_mode == 'vnested_fine' )  CALL pres
    1050 
    1051 !--             Anterpolate TKE, satisfy Germano Identity
    1052                 CALL cpu_log( log_point_s(28), 'vnest_anter_e', 'start' )
    1053                 CALL vnest_anterpolate_e
    1054                 CALL cpu_log( log_point_s(28), 'vnest_anter_e', 'stop' )
    1055 #else
    1056                 CONTINUE
     1012!--          Mass (volume) flux correction to ensure global mass conservation for child domains.
     1013             IF ( child_domain )  THEN
     1014                IF ( nesting_mode == 'vertical' )  THEN
     1015                   CALL pmci_ensure_nest_mass_conservation_vertical
     1016                ELSE
     1017                   CALL pmci_ensure_nest_mass_conservation
     1018                ENDIF
     1019             ENDIF
    10571020#endif
    1058 
    1059              ELSE
    1060 #if defined( __parallel )
    1061 !
    1062 !--             Mass (volume) flux correction to ensure global mass conservation for child domains.
    1063                 IF ( child_domain )  THEN
    1064                    IF ( nesting_mode == 'vertical' )  THEN
    1065                       CALL pmci_ensure_nest_mass_conservation_vertical
    1066                    ELSE
    1067                       CALL pmci_ensure_nest_mass_conservation
    1068                    ENDIF
    1069                 ENDIF
    1070 #endif
    1071                 CALL pres
    1072 
    1073              ENDIF
     1021             CALL pres
    10741022
    10751023          ENDIF
     
    11871135             ENDIF
    11881136             CALL cpu_log( log_point(17), 'diffusivities', 'stop' )
    1189 
    1190 #if defined( __parallel )
    1191 !
    1192 !--          Vertical nesting: set fine grid eddy viscosity top boundary condition
    1193              IF ( vnest_init )  CALL vnest_boundary_conds_khkm
    1194 #endif
    11951137
    11961138          ENDIF
     
    14021344!
    14031345!--    Data exchange between coupled models
    1404        IF ( coupling_mode /= 'uncoupled'  .AND.  run_coupled  .AND.  .NOT. vnested )  THEN
     1346       IF ( coupling_mode /= 'uncoupled'  .AND.  run_coupled )  THEN
    14051347          time_coupling = time_coupling + dt_3d
    14061348
     
    17411683!$ACC END DATA
    17421684
    1743 #if defined( __parallel )
    1744 !
    1745 !-- Vertical nesting: Deallocate variables initialized for vertical nesting
    1746     IF ( vnest_init )  CALL vnest_deallocate
    1747 #endif
    1748 
    17491685    IF ( myid == 0 )  CALL finish_progress_bar
    17501686
Note: See TracChangeset for help on using the changeset viewer.