Ignore:
Timestamp:
Apr 4, 2018 4:27:14 PM (6 years ago)
Author:
suehring
Message:

Bugfix in parallelization of synthetic turbulence generator; revision in control mimic of synthetic turbulence generator in case of RAN-LES nesting; checks for dynamic input file added; control mimic for topography input slightly revised.

File:
1 edited

Legend:

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

    r2938 r2945  
    2525! -----------------
    2626! $Id$
     27! - Mimic for topography input slightly revised, in order to enable consistency
     28!   checks
     29! - Add checks for dimensions in dynamic input file and move already existing
     30!   checks
     31!
     32! 2938 2018-03-27 15:52:42Z suehring
    2733! Initial read of geostrophic wind components from dynamic driver.
    2834!
     
    104110       INTEGER(iwp) :: nx                             !< dimension length in x
    105111       INTEGER(iwp) :: ny                             !< dimension length in y
     112       INTEGER(iwp) :: nz                             !< dimension length in z
    106113       REAL(wp), DIMENSION(:), ALLOCATABLE :: x       !< dimension array in x
    107114       REAL(wp), DIMENSION(:), ALLOCATABLE :: y       !< dimension array in y
     115       REAL(wp), DIMENSION(:), ALLOCATABLE :: z       !< dimension array in z
    108116    END TYPE dims_xy
    109117!
     
    316324!
    317325!-- Define variables
    318     TYPE(dims_xy)    ::  dim_static !< data structure for x, y-dimension in static input file
     326    TYPE(dims_xy)    ::  dim_static  !< data structure for x, y-dimension in static input file
    319327
    320328    TYPE(force_type) ::  force     !< data structure for data input at lateral and top boundaries (provided by Inifor) 
     
    16721680       REAL(wp) ::  dum           !< dummy variable to skip columns while reading topography file   
    16731681
    1674        IF ( TRIM( topography ) /= 'read_from_file' )  RETURN
    16751682
    16761683       DO  ii = 0, io_blocks-1
     
    16951702                CALL inquire_variable_names( id_topo, var_names )
    16961703!
    1697 !--             Read x, y - dimensions
     1704!--             Read x, y - dimensions. Only required for consistency checks.
    16981705                CALL get_dimension_length( id_topo, dim_static%nx, 'x' )
    16991706                CALL get_dimension_length( id_topo, dim_static%ny, 'y' )
     
    18301837!
    18311838!--          ASCII input
    1832              ELSE
     1839             ELSEIF ( TRIM( topography ) == 'read_from_file' )  THEN
    18331840
    18341841                OPEN( 90, FILE='TOPOGRAPHY_DATA'//TRIM( coupling_char ),       &
     
    20132020             CALL get_dimension_length( id_dynamic, init_3d%ny,  'y'  )
    20142021             CALL get_dimension_length( id_dynamic, init_3d%nyv, 'yv' )
    2015 !
    2016 !--          Check for correct horizontal dimension. Please note, u- and v-grid
    2017 !--          hase 1 grid point less on Inifor grid.
    2018              IF ( init_3d%nx-1 /= nx  .OR.  init_3d%nxu-1 /= nx - 1  .OR.      &
    2019                   init_3d%ny-1 /= ny  .OR.  init_3d%nyv-1 /= ny - 1 )  THEN
    2020                 message_string = 'Number of inifor grid points does not '  //  &
    2021                                  'match the number of numeric grid points.'
    2022                 CALL message( 'netcdf_data_input_mod', 'NDI003', 1, 2, 0, 6, 0 )
    2023              ENDIF
    20242022!
    20252023!--          Read vertical dimensions. Later, these are required for eventual
     
    23762374
    23772375       USE indices,                                                            &
    2378            ONLY:  nx, nxl, nxlu, nxr, ny, nyn, nys, nysv, nzb, nzt
     2376           ONLY:  nxl, nxlu, nxr, nyn, nys, nysv, nzb, nzt
    23792377
    23802378       IMPLICIT NONE
     
    27802778           ONLY:  initializing_actions, forcing, message_string
    27812779
     2780       USE indices,                                                            &
     2781           ONLY:  nx, ny, nz
     2782
    27822783       IMPLICIT NONE
    27832784
     
    27982799                           TRIM( coupling_char )
    27992800          CALL message( 'netcdf_data_input_mod', 'NDI010', 1, 2, 0, 6, 0 )
     2801       ENDIF
     2802!
     2803!--    Check for correct horizontal and vertical dimension.
     2804!--    Please note, u- and v-grid has 1 grid point less on Inifor grid.
     2805       IF ( init_3d%nx-1 /= nx  .OR.  init_3d%nxu-1 /= nx - 1  .OR.            &
     2806            init_3d%ny-1 /= ny  .OR.  init_3d%nyv-1 /= ny - 1 )  THEN
     2807          message_string = 'Number of inifor horizontal grid points does '  // &
     2808                           'not match the number of numeric grid points.'
     2809          CALL message( 'netcdf_data_input_mod', 'NDI003', 1, 2, 0, 6, 0 )
     2810       ENDIF
     2811
     2812       IF ( init_3d%nzu /= nz )  THEN
     2813          message_string = 'Number of inifor vertical grid points does '  // &
     2814                           'not match the number of numeric grid points.'
     2815          CALL message( 'netcdf_data_input_mod', 'NDI003', 1, 2, 0, 6, 0 )
    28002816       ENDIF
    28012817
Note: See TracChangeset for help on using the changeset viewer.