Changeset 2955 for palm/trunk/SOURCE


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

Location:
palm/trunk/SOURCE
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/Makefile

    r2938 r2955  
    2525# -----------------
    2626# $Id$
     27# Add log-points to measure CPU time of NetCDF data input.
     28#
     29# 2938 2018-03-27 15:52:42Z suehring
    2730# No initialization of child domains via dynamic input file, except for soil
    2831# moisture and temperature
     
    11691172        mod_kinds.o
    11701173netcdf_data_input_mod.o: \
     1174        cpulog_mod.o \
    11711175        mod_kinds.o \
    11721176        modules.o
  • 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
  • palm/trunk/SOURCE/netcdf_data_input_mod.f90

    r2953 r2955  
    2525! -----------------
    2626! $Id$
     27! Extend checks for consistent setting of buildings, its ID and type.
     28! Add log-points to measure CPU time of NetCDF data input.
     29!
     30! 2953 2018-04-09 11:26:02Z suehring
    2731! Bugfix in checks for initialization data
    2832!
     
    108112        ONLY:  coupling_char, io_blocks, io_group
    109113
     114    USE cpulog,                                                                &
     115        ONLY:  cpu_log, log_point_s
     116
    110117    USE kinds
    111118
     
    595602!--    If not static input file is available, skip this routine
    596603       IF ( .NOT. input_pids_static )  RETURN
     604!
     605!--    Measure CPU time
     606       CALL cpu_log( log_point_s(82), 'NetCDF input', 'start' )
    597607!
    598608!--    Read plant canopy variables.
     
    12151225#endif
    12161226       ENDDO
     1227!
     1228!--    End of CPU measurement
     1229       CALL cpu_log( log_point_s(82), 'NetCDF input', 'stop' )
    12171230!
    12181231!--    Exchange 1 ghost points for surface variables. Please note, ghost point
     
    16891702
    16901703       REAL(wp) ::  dum           !< dummy variable to skip columns while reading topography file   
    1691 
     1704!
     1705!--    CPU measurement
     1706       CALL cpu_log( log_point_s(83), 'NetCDF/ASCII input topo', 'start' )
    16921707
    16931708       DO  ii = 0, io_blocks-1
     
    18901905       ENDDO
    18911906!
     1907!--    End of CPU measurement
     1908       CALL cpu_log( log_point_s(83), 'NetCDF/ASCII input topo', 'stop' )
     1909!
    18921910!--    Check for minimum requirement to setup building topography. If buildings
    18931911!--    are provided, also an ID and a type are required.
     
    20022020       IF ( bc_lr_cyc  .AND.  nxl == 0 )  nxlu = 1 
    20032021       IF ( bc_ns_cyc  .AND.  nys == 0 )  nysv = 1
     2022
     2023!
     2024!--    CPU measurement
     2025       CALL cpu_log( log_point_s(85), 'NetCDF input init', 'start' )
    20042026
    20052027       DO  ii = 0, io_blocks-1
     
    23482370#endif
    23492371       ENDDO
     2372!
     2373!--    End of CPU measurement
     2374       CALL cpu_log( log_point_s(85), 'NetCDF input init', 'stop' )
    23502375!
    23512376!--    Finally, check if the input data has any fill values. Please note,
     
    24712496!--    Skip input if no forcing from larger-scale models is applied.
    24722497       IF ( .NOT. forcing )  RETURN
     2498
     2499!
     2500!--    CPU measurement
     2501       CALL cpu_log( log_point_s(86), 'NetCDF input forcing', 'start' )
    24732502
    24742503       DO  ii = 0, io_blocks-1
     
    28372866
    28382867!
     2868!--    End of CPU measurement
     2869       CALL cpu_log( log_point_s(86), 'NetCDF input forcing', 'stop' )
     2870
     2871!
    28392872!--    Finally, after data input set control flag indicating that vertical
    28402873!--    inter- and/or extrapolation is required.
     
    32503283             ENDIF
    32513284!
    3252 !--          Check if building_type is set at each building
     3285!--          Check if building_type is set at each building and vice versa.
    32533286             IF ( building_type_f%from_file  .AND.  buildings_f%from_file )  THEN
    32543287                IF ( buildings_f%lod == 1 )  THEN
    32553288                   IF ( buildings_f%var_2d(j,i)  /= buildings_f%fill1  .AND.   &
    32563289                        building_type_f%var(j,i) == building_type_f%fill )  THEN
    3257                       WRITE( message_string, * ) 'Each building requires ' //  &
    3258                                                  'a type in case the ' //      &
    3259                                                  'urban-surface model is ' //  &
    3260                                                  'applied. i, j = ', i, j
     3290
     3291                      WRITE( message_string, * ) 'Each location where a ' //   &
     3292                                         'building is set requires a type ' // &
     3293                                         '( and vice versa ) in case the ' //  &
     3294                                         'urban-surface model is applied. ' // &
     3295                                         'i, j = ', i, j
    32613296                      CALL message( 'netcdf_data_input_mod', 'NDI035',         &
    32623297                                     2, 2, 0, 6, 0 )
     
    32643299                ENDIF
    32653300                IF ( buildings_f%lod == 2 )  THEN
     3301                   IF ( ANY( buildings_f%var_3d(:,j,i) == 1 )  .AND.           &
     3302                        building_type_f%var(j,i) == building_type_f%fill )  THEN
     3303                      WRITE( message_string, * ) 'Each location where a ' //   &
     3304                                         'building is set requires a type ' // &
     3305                                         '( and vice versa ) in case the ' //  &
     3306                                         'urban-surface model is applied. ' // &
     3307                                         'i, j = ', i, j
     3308                      CALL message( 'netcdf_data_input_mod', 'NDI035',         &
     3309                                     2, 2, 0, 6, 0 )
     3310                   ENDIF
     3311                ENDIF
     3312             ENDIF
     3313!
     3314!--          Check if at each location where a building is present also an ID
     3315!--          is set and vice versa.
     3316             IF ( buildings_f%from_file )  THEN
     3317                IF ( buildings_f%lod == 1 )  THEN
     3318                   IF ( buildings_f%var_2d(j,i) /= buildings_f%fill1  .AND.    &
     3319                        building_id_f%var(j,i)  == building_id_f%fill )  THEN
     3320                      WRITE( message_string, * ) 'Each location where a ' //   &
     3321                                         'building is set requires an ID ' //  &
     3322                                         '( and vice versa ). i, j = ', i, j
     3323                      CALL message( 'netcdf_data_input_mod', 'NDI036',         &
     3324                                     2, 2, 0, 6, 0 )
     3325                   ENDIF
     3326                ELSEIF ( buildings_f%lod == 2 )  THEN
     3327                   IF ( ANY( buildings_f%var_3d(:,j,i) == 1 )  .AND.           &
     3328                        building_id_f%var(j,i) == building_id_f%fill )  THEN
     3329                      WRITE( message_string, * ) 'Each location where a ' //   &
     3330                                         'building is set requires an ID ' //  &
     3331                                         '( and vice versa ). i, j = ', i, j
     3332                      CALL message( 'netcdf_data_input_mod', 'NDI036',         &
     3333                                     2, 2, 0, 6, 0 )
     3334                   ENDIF
     3335                ENDIF
     3336             ENDIF
     3337!
     3338!--          Check if at each location where a building ID or a -type is set
     3339!--          also a bulding is defined.
     3340             IF ( buildings_f%from_file )  THEN
     3341                IF ( buildings_f%lod == 1 )  THEN
     3342                   IF ( buildings_f%var_2d(j,i)  /= buildings_f%fill1  .AND.   &
     3343                        building_id_f%var(j,i) == building_id_f%fill )  THEN
     3344                      WRITE( message_string, * ) 'Each building grid point '// &
     3345                                                 'requires an ID.', i, j
     3346                      CALL message( 'netcdf_data_input_mod', 'NDI036',         &
     3347                                     2, 2, 0, 6, 0 )
     3348                   ENDIF
     3349                ELSEIF ( buildings_f%lod == 2 )  THEN
    32663350                   IF ( ANY( buildings_f%var_3d(:,j,i) == 1 )                  &
    3267                   .AND. building_type_f%var(j,i) == building_type_f%fill )  THEN
    3268                       WRITE( message_string, * ) 'Each building requires ' //  &
    3269                                                  'a type in case the ' //      &
    3270                                                  'urban-surface model is ' //  &
    3271                                                  'applied. i, j = ', i, j
     3351                  .AND. building_id_f%var(j,i) == building_id_f%fill )  THEN
     3352                      WRITE( message_string, * ) 'Each building grid point '// &
     3353                                                 'requires an ID.', i, j
    32723354                      CALL message( 'netcdf_data_input_mod', 'NDI036',         &
    32733355                                     2, 2, 0, 6, 0 )
Note: See TracChangeset for help on using the changeset viewer.