Ignore:
Timestamp:
Aug 16, 2019 1:50:17 PM (5 years ago)
Author:
suehring
Message:

Replace get_topography_top_index functions by pre-calculated arrays in order to save computational resources

File:
1 edited

Legend:

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

    r4029 r4168  
    2525! -----------------
    2626! $Id$
     27! Replace function get_topography_top_index by topo_top_ind
     28!
     29! 4029 2019-06-14 14:04:35Z raasch
    2730! nest_chemistry switch removed
    2831!
     
    478481    USE indices,                                                               &
    479482        ONLY:  nbgp, nx, nxl, nxlg, nxlu, nxr, nxrg, ny, nyn, nyng, nys, nysg, &
    480                nysv, nz, nzb, nzt, wall_flags_0
     483               nysv, nz, nzb, nzt, topo_top_ind, wall_flags_0
    481484
    482485    USE bulk_cloud_model_mod,                                                  &
     
    528531
    529532    USE surface_mod,                                                           &
    530         ONLY:  get_topography_top_index_ji, surf_def_h, surf_lsm_h, surf_usm_h
     533        ONLY:  surf_def_h, surf_lsm_h, surf_usm_h
    531534
    532535    IMPLICIT NONE
     
    23792382          DO  j = nys, nyn
    23802383             sub_sum = 0.0_wp
    2381              k_wall = get_topography_top_index_ji( j, i, 'u' )
     2384             k_wall = topo_top_ind(j,i,1)
    23822385             DO   k = k_wall + 1, nzt
    23832386                sub_sum = sub_sum + dzw(k)
     
    24012404          DO  j = nys, nyn
    24022405             sub_sum = 0.0_wp
    2403              k_wall = get_topography_top_index_ji( j, i, 'u' )
     2406             k_wall = topo_top_ind(j,i,1)
    24042407             DO   k = k_wall + 1, nzt
    24052408                sub_sum = sub_sum + dzw(k)
     
    24232426          DO  i = nxl, nxr
    24242427             sub_sum = 0.0_wp
    2425              k_wall = get_topography_top_index_ji( j, i, 'v' )
     2428             k_wall = topo_top_ind(j,i,2)
    24262429             DO  k = k_wall + 1, nzt
    24272430                sub_sum = sub_sum + dzw(k)
     
    24452448          DO  i = nxl, nxr
    24462449             sub_sum = 0.0_wp
    2447              k_wall = get_topography_top_index_ji( j, i, 'v' )
     2450             k_wall = topo_top_ind(j,i,2)
    24482451             DO  k = k_wall + 1, nzt
    24492452                sub_sum = sub_sum + dzw(k)
Note: See TracChangeset for help on using the changeset viewer.