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/virtual_measurement_mod.f90

    r3988 r4168  
    2525! -----------------
    2626! $Id$
     27! Replace function get_topography_top_index by topo_top_ind
     28!
     29! 3988 2019-05-22 11:32:37Z kanani
    2730! Add variables to enable steering of output interval for virtual measurements
    2831!
     
    115118
    116119    USE indices,                                                               &
    117         ONLY:  nzb, nzt, nxl, nxr, nys, nyn, nx, ny, wall_flags_0
     120        ONLY:  nzb, nzt, nxl, nxr, nys, nyn, nx, ny, topo_top_ind, wall_flags_0
    118121
    119122    USE kinds
     
    435438               netcdf_data_input_get_dimension_length,                         &
    436439               netcdf_data_input_att, netcdf_data_input_var
    437                
    438     USE surface_mod,                                                           &
    439         ONLY:  get_topography_top_index_ji
    440440       
    441441    IMPLICIT NONE
     
    763763!--                Determine vertical index which correspond to the observation
    764764!--                height.
    765                    ksurf = get_topography_top_index_ji( js, is, 's' )
     765                   ksurf = topo_top_ind(js,is,0)
    766766                   ks = MINLOC( ABS( zu - zw(ksurf) - z_ag(t,n) ), DIM = 1 ) - 1
    767767!
     
    822822                      vmea(l)%j(ns) = j
    823823                      vmea(l)%k(ns) = k
    824                       vmea(l)%z_ag(ns)  = zu(k) -                              &
    825                                    zw(get_topography_top_index_ji( j, i, 's' ))
     824                      vmea(l)%z_ag(ns)  = zu(k) - zw(topo_top_ind(j,i,0))
    826825                   ENDIF
    827826                ENDDO
Note: See TracChangeset for help on using the changeset viewer.