Ignore:
Timestamp:
Apr 9, 2018 3:14:01 PM (6 years ago)
Author:
suehring
Message:

Revise topography filter; extend checks for consistent setting of building ID and type; add cpu measures in netcdf-data input

File:
1 edited

Legend:

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

    r2927 r2955  
    2525! -----------------
    2626! $Id$
     27! Improve topography filter routine and add ghost-point exchange for building
     28! ID and building type.
     29!
     30! 2927 2018-03-23 15:13:00Z suehring
    2731! Bugfix, setting boundary conditions for topography index array.
    2832!
     
    11861190    INTEGER(iwp) ::  num_wall   !< number of surrounding vertical walls for a single grid point
    11871191
    1188     INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  topo_tmp      !< temporary 3D-topography used to fill holes
    1189     INTEGER(iwp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  topo_3d       !< 3D-topography array merging buildings and orography
     1192    INTEGER(iwp), DIMENSION(nysg:nyng,nxlg:nxrg)           ::  var_exchange_int  !< dummy array for exchanging ghost-points
     1193    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE            ::  topo_tmp          !< temporary 3D-topography used to fill holes
     1194    INTEGER(iwp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  topo_3d           !< 3D-topography array merging buildings and orography
    11901195!
    11911196!-- Before checking for holes, set lateral boundary conditions for
     
    12011206       num_hole = 0   
    12021207       CALL exchange_horiz_int( topo_3d, nys, nyn, nxl, nxr, nzt, nbgp )
     1208!
     1209!--    Exchange also building ID and type. Note, building_type is an one-byte
     1210!--    variable.
     1211       IF ( building_id_f%from_file )                                          &
     1212          CALL exchange_horiz_2d_int( building_id_f%var, nys, nyn, nxl, nxr, nbgp )
     1213       IF ( building_type_f%from_file )  THEN
     1214          var_exchange_int = INT( building_type_f%var, KIND = 4 )
     1215          CALL exchange_horiz_2d_int( var_exchange_int, nys, nyn, nxl, nxr, nbgp )
     1216          building_type_f%var = INT( var_exchange_int, KIND = 1 )
     1217       ENDIF
    12031218
    12041219       topo_tmp = topo_3d
     
    13431358       IF ( nxl == 0  )  topo_3d(:,:,-1)   = topo_3d(:,:,0)
    13441359       IF ( nxr == nx )  topo_3d(:,:,nx+1) = topo_3d(:,:,nx)         
     1360    ENDIF
     1361!
     1362!-- Exchange building ID and type. Note, building_type is an one-byte variable.
     1363    IF ( building_id_f%from_file )                                             &
     1364       CALL exchange_horiz_2d_int( building_id_f%var, nys, nyn, nxl, nxr, nbgp )
     1365    IF ( building_type_f%from_file )  THEN
     1366       var_exchange_int = INT( building_type_f%var, KIND = 4 )
     1367       CALL exchange_horiz_2d_int( var_exchange_int, nys, nyn, nxl, nxr, nbgp )
     1368       building_type_f%var = INT( var_exchange_int, KIND = 1 )
    13451369    ENDIF
    13461370
Note: See TracChangeset for help on using the changeset viewer.