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

    r4159 r4168  
    2525! -----------------
    2626! $Id$
     27! Pre-calculate topography top index and store it on an array (replaces former
     28! functions get_topography_top_index)
     29!
     30! 4159 2019-08-15 13:31:35Z suehring
    2731! Revision of topography processing. This was not consistent between 2D and 3D
    2832! buildings.
     
    420424               nzb_max, nzb_s_inner, nzb_s_outer, nzb_u_inner,                 &
    421425               nzb_u_outer, nzb_v_inner, nzb_v_outer, nzb_w_inner,             &
    422                nzb_w_outer, nzt, topo_min_level
     426               nzb_w_outer, nzt, topo_top_ind, topo_min_level
    423427   
    424428    USE kinds
     
    429433
    430434    USE surface_mod,                                                           &
    431         ONLY:  get_topography_top_index, get_topography_top_index_ji, init_bc
     435        ONLY:  init_bc
    432436
    433437    USE vertical_nesting_mod,                                                  &
     
    919923    topo_min_level   = 0
    920924#if defined( __parallel )
    921     CALL MPI_ALLREDUCE( MINVAL( get_topography_top_index( 's' ) ),             &
     925    CALL MPI_ALLREDUCE( MINVAL( topo_top_ind(nys:nyn,nxl:nxr,0) ),             &
    922926                        topo_min_level, 1, MPI_INTEGER, MPI_MIN, comm2d, ierr )
    923927#else
    924     topo_min_level = MINVAL( get_topography_top_index( 's' ) )
     928    topo_min_level = MINVAL( topo_top_ind(nys:nyn,nxl:nxr,0) )
    925929#endif
    926930!
     
    960964!--          Topography height on scalar grid. Therefore, determine index of
    961965!--          upward-facing surface element on scalar grid.
    962              zu_s_inner(i,j) = zu( get_topography_top_index_ji( j, i, 's' ) )
     966             zu_s_inner(i,j) = zu(topo_top_ind(j,i,0))
    963967!
    964968!--          Topography height on w grid. Therefore, determine index of
    965969!--          upward-facing surface element on w grid.
    966              zw_w_inner(i,j) = zw( get_topography_top_index_ji( j, i, 's' ) )
     970             zw_w_inner(i,j) = zw(topo_top_ind(j,i,3))
    967971          ENDDO
    968972       ENDDO
     
    988992!
    989993!-- Initialize 2D-index arrays. Note, these will be removed soon!
    990     nzb_local(nys:nyn,nxl:nxr) = get_topography_top_index( 's' )
     994    nzb_local(nys:nyn,nxl:nxr) = topo_top_ind(nys:nyn,nxl:nxr,0)
    991995    CALL exchange_horiz_2d_int( nzb_local, nys, nyn, nxl, nxr, nbgp )
    992996!
     
    9961000    IF ( TRIM( topography ) /= 'flat' )  THEN
    9971001#if defined( __parallel )
    998        CALL MPI_ALLREDUCE( MAXVAL( get_topography_top_index( 's' ) ),          &
     1002       CALL MPI_ALLREDUCE( MAXVAL( topo_top_ind(nys:nyn,nxl:nxr,0) ),          &
    9991003                           nzb_local_max, 1, MPI_INTEGER, MPI_MAX, comm2d, ierr )               
    10001004#else
    1001        nzb_local_max = MAXVAL( get_topography_top_index( 's' ) )
     1005       nzb_local_max = MAXVAL( topo_top_ind(nys:nyn,nxl:nxr,0) )
    10021006#endif
    10031007       nzb_local_min = topo_min_level
     
    20172021    USE pegrid
    20182022
    2019     USE surface_mod,                                                           &
    2020         ONLY:  get_topography_top_index, get_topography_top_index_ji
    2021 
    20222023    IMPLICIT NONE
    20232024
     
    25722573    USE indices,                                                               &
    25732574        ONLY:  nbgp, nx, nxl, nxlg, nxr, nxrg, ny, nyn, nyng, nys, nysg, nzb,  &
    2574                nzt, wall_flags_0
     2575               nzt, topo_top_ind, wall_flags_0
    25752576
    25762577    USE kinds
     
    25792580
    25802581    INTEGER(iwp) ::  i             !< index variable along x
     2582    INTEGER(iwp) ::  ibit          !< integer bit position of topgraphy masking array
    25812583    INTEGER(iwp) ::  j             !< index variable along y
    25822584    INTEGER(iwp) ::  k             !< index variable along z
     
    28852887       ENDIF     
    28862888    ENDIF
    2887 
     2889!
     2890!-- Pre-calculate topography top indices (former get_topography_top_index
     2891!-- function)
     2892    ALLOCATE( topo_top_ind(nysg:nyng,nxlg:nxrg,0:4) )
     2893!
     2894!-- Uppermost topography index on scalar grid
     2895    ibit = 12
     2896    topo_top_ind(:,:,0) = MAXLOC(                                              &
     2897                                  MERGE( 1, 0,                                 &
     2898                                          BTEST( wall_flags_0(:,:,:), ibit )   &
     2899                                       ), DIM = 1                              &
     2900                                ) - 1
     2901!
     2902!-- Uppermost topography index on u grid
     2903    ibit = 14
     2904    topo_top_ind(:,:,1) = MAXLOC(                                              &
     2905                                  MERGE( 1, 0,                                 &
     2906                                          BTEST( wall_flags_0(:,:,:), ibit )   &
     2907                                       ), DIM = 1                              &
     2908                                ) - 1
     2909!
     2910!-- Uppermost topography index on v grid
     2911    ibit = 16
     2912    topo_top_ind(:,:,2) = MAXLOC(                                              &
     2913                                  MERGE( 1, 0,                                 &
     2914                                          BTEST( wall_flags_0(:,:,:), ibit )   &
     2915                                       ), DIM = 1                              &
     2916                                ) - 1
     2917!
     2918!-- Uppermost topography index on w grid
     2919    ibit = 18
     2920    topo_top_ind(:,:,3) = MAXLOC(                                              &
     2921                                  MERGE( 1, 0,                                 &
     2922                                          BTEST( wall_flags_0(:,:,:), ibit )   &
     2923                                       ), DIM = 1                              &
     2924                                ) - 1
     2925!
     2926!-- Uppermost topography index on scalar outer grid
     2927    ibit = 24
     2928    topo_top_ind(:,:,4) = MAXLOC(                                              &
     2929                                  MERGE( 1, 0,                                 &
     2930                                          BTEST( wall_flags_0(:,:,:), ibit )   &
     2931                                       ), DIM = 1                              &
     2932                                ) - 1                           
    28882933
    28892934 END SUBROUTINE set_topo_flags
Note: See TracChangeset for help on using the changeset viewer.