Changeset 2787 for palm


Ignore:
Timestamp:
Feb 5, 2018 8:06:52 PM (6 years ago)
Author:
suehring
Message:

Check if 3D building input is consistent to numeric grid.

File:
1 edited

Legend:

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

    r2773 r2787  
    2525! -----------------
    2626! $Id$
     27! Check if 3D building input is consistent to numeric grid.
     28!
     29! 2773 2018-01-30 14:12:54Z suehring
    2730! - Enable initialization with 3D topography.
    2831! - Move check for correct initialization in nesting mode to check_parameters.
     
    230233       INTEGER(iwp)    ::  nz                                    !< number of vertical layers in file
    231234       INTEGER(KIND=1), DIMENSION(:,:,:), ALLOCATABLE ::  var_3d !< 3d variable (lod = 2)
     235
     236       REAL(wp), DIMENSION(:), ALLOCATABLE ::  z                 !< vertical coordinate for 3D building, used for consistency check
    232237
    233238       LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used 
     
    17151720 
    17161721                   IF ( buildings_f%lod == 2 )  THEN
    1717                       ALLOCATE( buildings_f%var_3d(nzb:buildings_f%nz,         &
     1722                      ALLOCATE( buildings_f%z(nzb:buildings_f%nz-1) )
     1723                      CALL get_variable( id_topo, 'z', buildings_f%z )
     1724
     1725                      ALLOCATE( buildings_f%var_3d(nzb:buildings_f%nz-1,       &
    17181726                                                   nys:nyn,nxl:nxr) )
    17191727                      buildings_f%var_3d = 0
     
    27242732    SUBROUTINE netcdf_data_input_check_static
    27252733
     2734       USE arrays_3d,                                                          &
     2735           ONLY:  zu
     2736
    27262737       USE control_parameters,                                                 &
    27272738           ONLY:  land_surface, message_string, urban_surface
     
    27502761          CALL message( 'netcdf_data_input_mod', 'PA0999', 2, 2, 0, 6, 0 )
    27512762       ENDIF
     2763!
     2764!--    If 3D buildings are read, check if building information is consistent
     2765!--    to numeric grid.
     2766       IF ( buildings_f%from_file )  THEN
     2767          IF ( buildings_f%lod == 2 )  THEN
     2768             IF ( buildings_f%nz > SIZE( zu ) )  THEN
     2769                message_string = 'Reading 3D building data - too much ' //     &
     2770                                 'data points along the vertical coordinate.'
     2771                CALL message( 'netcdf_data_input_mod', 'PA0999', 2, 2, 0, 6, 0 )
     2772             ENDIF
     2773
     2774             IF ( ANY( buildings_f%z(0:buildings_f%nz-1) /=                    &
     2775                       zu(0:buildings_f%nz-1) ) )  THEN
     2776                message_string = 'Reading 3D building data - vertical ' //     &
     2777                                 'coordinate do not match numeric grid.'
     2778                CALL message( 'netcdf_data_input_mod', 'PA0999', 2, 2, 0, 6, 0 )
     2779             ENDIF
     2780          ENDIF
     2781       ENDIF
     2782
    27522783!
    27532784!--    Skip further checks concerning buildings and natural surface properties
Note: See TracChangeset for help on using the changeset viewer.