Ignore:
Timestamp:
Aug 16, 2019 1:50:17 PM (4 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/nesting_offl_mod.f90

    r4125 r4168  
    2525! -----------------
    2626! $Id$
     27! Replace function get_topography_top_index by topo_top_ind
     28!
     29! 4125 2019-07-29 13:31:44Z suehring
    2730! In order to enable netcdf parallel access, allocate dummy arrays for the
    2831! lateral boundary data on cores that actually do not belong to these
     
    119122    USE indices,                                                               &
    120123        ONLY:  nbgp, nx, nxl, nxlg, nxlu, nxr, nxrg, ny, nys,                  &
    121                nysv, nysg, nyn, nyng, nzb, nz, nzt, wall_flags_0
     124               nysv, nysg, nyn, nyng, nzb, nz, nzt,                            &
     125               topo_top_ind,                                                   &
     126               wall_flags_0
    122127
    123128    USE kinds
     
    873878       
    874879       USE kinds
    875        
    876        USE surface_mod,                                                        &
    877            ONLY:  get_topography_top_index, get_topography_top_index_ji
    878880
    879881       IMPLICIT NONE
     
    918920!
    919921!--          Determine topography top index at current (j,i) index
    920              k_surface = get_topography_top_index_ji( j, i, 's' )
     922             k_surface = topo_top_ind(j,i,0)
    921923!
    922924!--          Pre-compute surface virtual temperature. Therefore, use 2nd
     
    978980       
    979981          DO  i = nxl, nxr
    980              k_surface = get_topography_top_index_ji( j, i, 's' )
     982             k_surface = topo_top_ind(j,i,0)
    981983 
    982984             IF ( humidity )  THEN
     
    10321034!--    turbulence generator accordingly. If Rayleigh damping would be applied
    10331035!--    near buildings, etc., this would spoil the simulation results.
    1034        topo_max_l = zw(MAXVAL( get_topography_top_index( 's' )))
     1036       topo_max_l = zw(MAXVAL( topo_top_ind(nys:nyn,nxl:nxr,0) ))
    10351037       
    10361038#if defined( __parallel )
Note: See TracChangeset for help on using the changeset viewer.