Ignore:
Timestamp:
Aug 27, 2018 4:58:37 PM (6 years ago)
Author:
suehring
Message:

Additional namelist parameter to switch on/off the nesting of chemical species; Enable the input of soil data from dynamic input files independent on atmosphere in order to initialize soil properties in nested child domains from dynamic input; Revise error message number for static/dynamic input; Revise and add checks for static/dynamic input; Bugfix, add netcdf4_parallel directive for collective read operation

File:
1 edited

Legend:

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

    r3186 r3209  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! - Separate input of soil properties from input of atmospheric data. This
     23!   enables input of soil properties also in child domains without any
     24!   dependence on atmospheric input
     25! - Check for missing initial 1D/3D data in dynamic input file
     26! - Revise checks for matching grid spacing in model and input file
     27! - Bugfix, add netcdf4_parallel directive for collective read operation
     28! - Revise error message numbers
    2329!
    2430! Former revisions:
     
    303309       REAL(wp) ::  rotation_angle   !< rotation angle of input data
    304310
    305        REAL(wp), DIMENSION(:), ALLOCATABLE ::  msoil_init   !< initial vertical profile of soil moisture
     311       REAL(wp), DIMENSION(:), ALLOCATABLE ::  msoil_1d     !< initial vertical profile of soil moisture
    306312       REAL(wp), DIMENSION(:), ALLOCATABLE ::  pt_init      !< initial vertical profile of pt
    307313       REAL(wp), DIMENSION(:), ALLOCATABLE ::  q_init       !< initial vertical profile of q
    308        REAL(wp), DIMENSION(:), ALLOCATABLE ::  tsoil_init   !< initial vertical profile of soil temperature
     314       REAL(wp), DIMENSION(:), ALLOCATABLE ::  tsoil_1d     !< initial vertical profile of soil temperature
    309315       REAL(wp), DIMENSION(:), ALLOCATABLE ::  u_init       !< initial vertical profile of u
    310316       REAL(wp), DIMENSION(:), ALLOCATABLE ::  ug_init      !< initial vertical profile of ug
     
    317323
    318324
    319        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  msoil        !< initial 3d soil moisture provide by Inifor and interpolated onto soil grid
    320        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  tsoil        !< initial 3d soil temperature provide by Inifor and interpolated onto soil grid
     325       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  msoil_3d !< initial 3d soil moisture provide by Inifor and interpolated onto soil grid
     326       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  tsoil_3d !< initial 3d soil temperature provide by Inifor and interpolated onto soil grid
    321327
    322328    END TYPE init_type
     
    573579       MODULE PROCEDURE netcdf_data_input_init_3d
    574580    END INTERFACE netcdf_data_input_init_3d
     581   
     582    INTERFACE netcdf_data_input_init_lsm
     583       MODULE PROCEDURE netcdf_data_input_init_lsm
     584    END INTERFACE netcdf_data_input_init_lsm
    575585
    576586    INTERFACE netcdf_data_input_lsf
     
    595605       MODULE PROCEDURE get_variable_3d_real
    596606       MODULE PROCEDURE get_variable_3d_real_dynamic
    597 !        MODULE PROCEDURE get_variable_3d_real_v
    598607       MODULE PROCEDURE get_variable_4d_real
    599608    END INTERFACE get_variable
     
    626635    PUBLIC netcdf_data_input_check_dynamic, netcdf_data_input_check_static,    &
    627636           netcdf_data_input_inquire_file,                                     &
    628            netcdf_data_input_init, netcdf_data_input_init_3d,                  &
     637           netcdf_data_input_init, netcdf_data_input_init_lsm,                 &
     638           netcdf_data_input_init_3d,                                          &
    629639           netcdf_data_input_interpolate, netcdf_data_input_lsf,               &
    630640           netcdf_data_input_surface_data, netcdf_data_input_topo
     
    18641874                                 '(level of detail) is not set ' //            &
    18651875                                 'properly for buildings_2d.'
    1866                 CALL message( 'netcdf_data_input_mod', 'NDI000',               &
     1876                CALL message( 'netcdf_data_input_mod', 'PA0540',               &
    18671877                               1, 2, 0, 6, 0 )
    18681878             ENDIF
     
    18971907                                 '(level of detail) is not set ' //            &
    18981908                                 'properly for buildings_3d.'
    1899                 CALL message( 'netcdf_data_input_mod', 'NDI001',               &
     1909                CALL message( 'netcdf_data_input_mod', 'PA0541',               &
    19001910                               1, 2, 0, 6, 0 )
    19011911             ENDIF
     
    19992009             message_string = 'If building heigths are prescribed in ' //      &
    20002010                              'static input file, also an ID is required.'
    2001              CALL message( 'netcdf_data_input_mod', 'NDI002', 1, 2, 0, 6, 0 )
     2011             CALL message( 'netcdf_data_input_mod', 'PA0542', 1, 2, 0, 6, 0 )
    20022012          ENDIF
    20032013       ENDIF
     
    21202130       CALL inquire_variable_names( id_dynamic, var_names )
    21212131!
    2122 !--    Read vertical dimension of scalar und w grid. Will be used for
    2123 !--    inter- and extrapolation in case of stretched numeric grid.
    2124 !--    This will be removed when Inifor is able to handle stretched grids.
     2132!--    Read vertical dimension of scalar und w grid.
    21252133       CALL get_dimension_length( id_dynamic, init_3d%nzu, 'z'     )
    21262134       CALL get_dimension_length( id_dynamic, init_3d%nzw, 'zw'    )
    2127        IF ( check_existence( var_names, 'zsoil' ) )                            &
    2128           CALL get_dimension_length( id_dynamic, init_3d%nzs, 'zsoil' )
    21292135!
    21302136!--    Read also the horizontal dimensions. These are used just used fo
     
    21462152                           'does not match the number of numeric grid '//      &
    21472153                           'points.'
    2148           CALL message( 'netcdf_data_input_mod', 'NDI003', 1, 2, 0, 6, 0 )
     2154          CALL message( 'netcdf_data_input_mod', 'PA0543', 1, 2, 0, 6, 0 )
    21492155       ENDIF
    21502156
     
    21532159                           'does not match the number of numeric grid '//      &
    21542160                           'points.'
    2155           CALL message( 'netcdf_data_input_mod', 'NDI003', 1, 2, 0, 6, 0 )
     2161          CALL message( 'netcdf_data_input_mod', 'PA0543', 1, 2, 0, 6, 0 )
    21562162       ENDIF
    21572163!
     
    21652171          ALLOCATE( init_3d%zw_atmos(1:init_3d%nzw) )
    21662172          CALL get_variable( id_dynamic, 'zw', init_3d%zw_atmos )
    2167        ENDIF
    2168        IF ( check_existence( var_names, 'zsoil' ) )  THEN
    2169           ALLOCATE( init_3d%z_soil(1:init_3d%nzs) )
    2170           CALL get_variable( id_dynamic, 'zsoil', init_3d%z_soil )
    21712173       ENDIF
    21722174!
     
    21842186          message_string = 'Vertical grid in dynamic driver does not '// &
    21852187                           'match the numeric grid.'
    2186           CALL message( 'netcdf_data_input_mod', 'NDI003', 1, 2, 0, 6, 0 )
     2188          CALL message( 'netcdf_data_input_mod', 'PA0543', 1, 2, 0, 6, 0 )
    21872189       ENDIF
    21882190!
     
    22642266          ENDIF
    22652267          init_3d%from_file_u = .TRUE.
     2268       ELSE
     2269          message_string = 'Missing initial data for u-component'
     2270          CALL message( 'netcdf_data_input_mod', 'PA0544', 1, 2, 0, 6, 0 )
    22662271       ENDIF
    22672272!
     
    23072312          ENDIF
    23082313          init_3d%from_file_v = .TRUE.
     2314       ELSE
     2315          message_string = 'Missing initial data for v-component'
     2316          CALL message( 'netcdf_data_input_mod', 'PA0544', 1, 2, 0, 6, 0 )
    23092317       ENDIF
    23102318!
     
    23452353          ENDIF
    23462354          init_3d%from_file_w = .TRUE.
     2355       ELSE
     2356          message_string = 'Missing initial data for w-component'
     2357          CALL message( 'netcdf_data_input_mod', 'PA0544', 1, 2, 0, 6, 0 )
    23472358       ENDIF
    23482359!
     
    23852396             ENDIF
    23862397             init_3d%from_file_pt = .TRUE.
     2398          ELSE
     2399             message_string = 'Missing initial data for ' //                   &
     2400                              'potential temperature'
     2401             CALL message( 'netcdf_data_input_mod', 'PA0544', 1, 2, 0, 6, 0 )
    23872402          ENDIF
    23882403       ENDIF
     
    24252440             ENDIF
    24262441             init_3d%from_file_q = .TRUE.
    2427           ENDIF
    2428        ENDIF
    2429 !
    2430 !--    Read soil moisture
    2431        IF ( land_surface )  THEN
    2432 
    2433           IF ( check_existence( var_names, 'init_soil_m' ) )  THEN
    2434 !
    2435 !--          Read attributes for the fill value and level-of-detail
    2436              CALL get_attribute( id_dynamic, char_fill,                        &
    2437                                  init_3d%fill_msoil,                           &
    2438                                  .FALSE., 'init_soil_m' )
    2439              CALL get_attribute( id_dynamic, char_lod,                         &
    2440                                  init_3d%lod_msoil,                            &
    2441                                  .FALSE., 'init_soil_m' )
    2442 !
    2443 !--          level-of-detail 1 - read initialization profile
    2444              IF ( init_3d%lod_msoil == 1 )  THEN
    2445                 ALLOCATE( init_3d%msoil_init(0:init_3d%nzs-1) )
    2446 
    2447                 CALL get_variable( id_dynamic, 'init_soil_m',                  &
    2448                                    init_3d%msoil_init(0:init_3d%nzs-1) )
    2449 !
    2450 !--          level-of-detail 2 - read 3D initialization data
    2451              ELSEIF ( init_3d%lod_msoil == 2 )  THEN
    2452                 ALLOCATE ( init_3d%msoil(0:init_3d%nzs-1,nys:nyn,nxl:nxr) )
    2453 
    2454                CALL get_variable( id_dynamic, 'init_soil_m',                   &   
    2455                                 init_3d%msoil(0:init_3d%nzs-1,nys:nyn,nxl:nxr),&
    2456                                 nxl, nxr, nys, nyn, 0, init_3d%nzs-1 )
    2457 
    2458              ENDIF
    2459              init_3d%from_file_msoil = .TRUE.
    2460           ENDIF
    2461 !
    2462 !--       Read soil temperature
    2463           IF ( check_existence( var_names, 'init_soil_t' ) )  THEN
    2464 !
    2465 !--          Read attributes for the fill value and level-of-detail
    2466              CALL get_attribute( id_dynamic, char_fill,                        &
    2467                                  init_3d%fill_tsoil,                           &
    2468                                  .FALSE., 'init_soil_t' )
    2469              CALL get_attribute( id_dynamic, char_lod,                         &
    2470                                  init_3d%lod_tsoil,                            &
    2471                                  .FALSE., 'init_soil_t' )
    2472 !
    2473 !--          level-of-detail 1 - read initialization profile
    2474              IF ( init_3d%lod_tsoil == 1 )  THEN
    2475                 ALLOCATE( init_3d%tsoil_init(0:init_3d%nzs-1) )
    2476 
    2477                 CALL get_variable( id_dynamic, 'init_soil_t',                  &
    2478                                    init_3d%tsoil_init(0:init_3d%nzs-1) )
    2479 
    2480 !
    2481 !--          level-of-detail 2 - read 3D initialization data
    2482              ELSEIF ( init_3d%lod_tsoil == 2 )  THEN
    2483                 ALLOCATE ( init_3d%tsoil(0:init_3d%nzs-1,nys:nyn,nxl:nxr) )
    2484                
    2485                 CALL get_variable( id_dynamic, 'init_soil_t',                  &   
    2486                                 init_3d%tsoil(0:init_3d%nzs-1,nys:nyn,nxl:nxr),&
    2487                                 nxl, nxr, nys, nyn, 0, init_3d%nzs-1 )
    2488              ENDIF
    2489              init_3d%from_file_tsoil = .TRUE.
     2442          ELSE
     2443             message_string = 'Missing initial data for ' //                   &
     2444                              'mixing ratio'
     2445             CALL message( 'netcdf_data_input_mod', 'PA0544', 1, 2, 0, 6, 0 )
    24902446          ENDIF
    24912447       ENDIF
     
    25122468             message_string = 'NetCDF input for init_atmosphere_u must ' //    &
    25132469                              'not contain any _FillValues'
    2514              CALL message( 'netcdf_data_input_mod', 'NDI004', 2, 2, 0, 6, 0 )
     2470             CALL message( 'netcdf_data_input_mod', 'PA0545', 2, 2, 0, 6, 0 )
    25152471          ENDIF
    25162472       ENDIF
     
    25282484             message_string = 'NetCDF input for init_atmosphere_v must ' //    &
    25292485                              'not contain any _FillValues'
    2530              CALL message( 'netcdf_data_input_mod', 'NDI005', 2, 2, 0, 6, 0 )
     2486             CALL message( 'netcdf_data_input_mod', 'PA0545', 2, 2, 0, 6, 0 )
    25312487          ENDIF
    25322488       ENDIF
     
    25442500             message_string = 'NetCDF input for init_atmosphere_w must ' //    &
    25452501                              'not contain any _FillValues'
    2546              CALL message( 'netcdf_data_input_mod', 'NDI006', 2, 2, 0, 6, 0 )
     2502             CALL message( 'netcdf_data_input_mod', 'PA0545', 2, 2, 0, 6, 0 )
    25472503          ENDIF
    25482504       ENDIF
     
    25602516             message_string = 'NetCDF input for init_atmosphere_pt must ' //   &
    25612517                              'not contain any _FillValues'
    2562              CALL message( 'netcdf_data_input_mod', 'NDI007', 2, 2, 0, 6, 0 )
     2518             CALL message( 'netcdf_data_input_mod', 'PA0545', 2, 2, 0, 6, 0 )
    25632519          ENDIF
    25642520       ENDIF
     
    25762532             message_string = 'NetCDF input for init_atmosphere_q must ' //    &
    25772533                              'not contain any _FillValues'
    2578              CALL message( 'netcdf_data_input_mod', 'NDI008', 2, 2, 0, 6, 0 )
     2534             CALL message( 'netcdf_data_input_mod', 'PA0545', 2, 2, 0, 6, 0 )
    25792535          ENDIF
    25802536       ENDIF
     
    25852541
    25862542    END SUBROUTINE netcdf_data_input_init_3d
     2543   
     2544!------------------------------------------------------------------------------!
     2545! Description:
     2546! ------------
     2547!> Reads initialization data of u, v, w, pt, q, geostrophic wind components,
     2548!> as well as soil moisture and soil temperature, derived from larger-scale
     2549!> model (COSMO) by Inifor.
     2550!------------------------------------------------------------------------------!
     2551    SUBROUTINE netcdf_data_input_init_lsm
     2552
     2553       USE arrays_3d,                                                          &
     2554           ONLY:  q, pt, u, v, w, zu, zw
     2555
     2556       USE control_parameters,                                                 &
     2557           ONLY:  bc_lr_cyc, bc_ns_cyc, humidity, land_surface, message_string,&
     2558                  nesting_offline, neutral, surface_pressure
     2559
     2560       USE indices,                                                            &
     2561           ONLY:  nx, nxl, nxlu, nxr, ny, nyn, nys, nysv, nzb, nz, nzt
     2562
     2563       IMPLICIT NONE
     2564
     2565       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names
     2566     
     2567       INTEGER(iwp) ::  id_dynamic !< NetCDF id of dynamic input file
     2568       INTEGER(iwp) ::  num_vars   !< number of variables in netcdf input file
     2569
     2570!
     2571!--    Skip routine if no input file with dynamic input data is available.
     2572       IF ( .NOT. input_pids_dynamic )  RETURN
     2573!
     2574!--    CPU measurement
     2575       CALL cpu_log( log_point_s(85), 'NetCDF input init', 'start' )
     2576
     2577#if defined ( __netcdf )
     2578!
     2579!--    Open file in read-only mode
     2580       CALL open_read_file( TRIM( input_file_dynamic ) //                      &
     2581                            TRIM( coupling_char ), id_dynamic )
     2582
     2583!
     2584!--    At first, inquire all variable names.
     2585       CALL inquire_num_variables( id_dynamic, num_vars )
     2586!
     2587!--    Allocate memory to store variable names.
     2588       ALLOCATE( var_names(1:num_vars) )
     2589       CALL inquire_variable_names( id_dynamic, var_names )
     2590!
     2591!--    Read vertical dimension for soil depth.
     2592       IF ( check_existence( var_names, 'zsoil' ) )                            &
     2593          CALL get_dimension_length( id_dynamic, init_3d%nzs, 'zsoil' )
     2594!
     2595!--    Read also the horizontal dimensions required for soil initialization.
     2596!--    Please note, in case of non-nested runs or in case of root domain,
     2597!--    these data is already available, but will be read again for the sake
     2598!--    of clearness.
     2599       CALL get_dimension_length( id_dynamic, init_3d%nx,  'x'  )
     2600       CALL get_dimension_length( id_dynamic, init_3d%ny,  'y'  )
     2601!
     2602!--    Check for correct horizontal and vertical dimension. Please note,
     2603!--    in case of non-nested runs or in case of root domain, these checks
     2604!--    are already performed
     2605       IF ( init_3d%nx-1 /= nx  .OR.  init_3d%ny-1 /= ny )  THEN
     2606          message_string = 'Number of inifor horizontal grid points  '//       &
     2607                           'does not match the number of numeric grid points.'
     2608          CALL message( 'netcdf_data_input_mod', 'PA0543', 1, 2, 0, 6, 0 )
     2609       ENDIF
     2610!
     2611!--    Read vertical dimensions. Later, these are required for eventual
     2612!--    inter- and extrapolations of the initialization data.
     2613       IF ( check_existence( var_names, 'zsoil' ) )  THEN
     2614          ALLOCATE( init_3d%z_soil(1:init_3d%nzs) )
     2615          CALL get_variable( id_dynamic, 'zsoil', init_3d%z_soil )
     2616       ENDIF
     2617!
     2618!--    Read initial data for soil moisture
     2619       IF ( check_existence( var_names, 'init_soil_m' ) )  THEN
     2620!
     2621!--       Read attributes for the fill value and level-of-detail
     2622          CALL get_attribute( id_dynamic, char_fill,                           &
     2623                              init_3d%fill_msoil,                              &
     2624                              .FALSE., 'init_soil_m' )
     2625          CALL get_attribute( id_dynamic, char_lod,                            &
     2626                              init_3d%lod_msoil,                               &
     2627                              .FALSE., 'init_soil_m' )
     2628!
     2629!--       level-of-detail 1 - read initialization profile
     2630          IF ( init_3d%lod_msoil == 1 )  THEN
     2631             ALLOCATE( init_3d%msoil_1d(0:init_3d%nzs-1) )
     2632
     2633             CALL get_variable( id_dynamic, 'init_soil_m',                     &
     2634                                init_3d%msoil_1d(0:init_3d%nzs-1) )
     2635!
     2636!--       level-of-detail 2 - read 3D initialization data
     2637          ELSEIF ( init_3d%lod_msoil == 2 )  THEN
     2638             ALLOCATE ( init_3d%msoil_3d(0:init_3d%nzs-1,nys:nyn,nxl:nxr) )
     2639
     2640            CALL get_variable( id_dynamic, 'init_soil_m',                      &   
     2641                             init_3d%msoil_3d(0:init_3d%nzs-1,nys:nyn,nxl:nxr),&
     2642                             nxl, nxr, nys, nyn, 0, init_3d%nzs-1 )
     2643
     2644          ENDIF
     2645          init_3d%from_file_msoil = .TRUE.
     2646       ENDIF
     2647!
     2648!--    Read soil temperature
     2649       IF ( check_existence( var_names, 'init_soil_t' ) )  THEN
     2650!
     2651!--       Read attributes for the fill value and level-of-detail
     2652          CALL get_attribute( id_dynamic, char_fill,                           &
     2653                              init_3d%fill_tsoil,                              &
     2654                              .FALSE., 'init_soil_t' )
     2655          CALL get_attribute( id_dynamic, char_lod,                            &
     2656                              init_3d%lod_tsoil,                               &
     2657                              .FALSE., 'init_soil_t' )
     2658!
     2659!--       level-of-detail 1 - read initialization profile
     2660          IF ( init_3d%lod_tsoil == 1 )  THEN
     2661             ALLOCATE( init_3d%tsoil_1d(0:init_3d%nzs-1) )
     2662
     2663             CALL get_variable( id_dynamic, 'init_soil_t',                     &
     2664                                init_3d%tsoil_1d(0:init_3d%nzs-1) )
     2665
     2666!
     2667!--       level-of-detail 2 - read 3D initialization data
     2668          ELSEIF ( init_3d%lod_tsoil == 2 )  THEN
     2669             ALLOCATE ( init_3d%tsoil_3d(0:init_3d%nzs-1,nys:nyn,nxl:nxr) )
     2670             
     2671             CALL get_variable( id_dynamic, 'init_soil_t',                     &   
     2672                             init_3d%tsoil_3d(0:init_3d%nzs-1,nys:nyn,nxl:nxr),&
     2673                             nxl, nxr, nys, nyn, 0, init_3d%nzs-1 )
     2674          ENDIF
     2675          init_3d%from_file_tsoil = .TRUE.
     2676       ENDIF
     2677!
     2678!--    Close input file
     2679       CALL close_input_file( id_dynamic )
     2680#endif
     2681!
     2682!--    End of CPU measurement
     2683       CALL cpu_log( log_point_s(85), 'NetCDF input init', 'stop' )
     2684
     2685    END SUBROUTINE netcdf_data_input_init_lsm   
    25872686
    25882687!------------------------------------------------------------------------------!
     
    28892988                            'input file ' //                                   &
    28902989                            TRIM( input_file_dynamic ) // TRIM( coupling_char )
    2891           CALL message( 'netcdf_data_input_mod', 'NDI009', 1, 2, 0, 6, 0 )
     2990          CALL message( 'netcdf_data_input_mod', 'PA0546', 1, 2, 0, 6, 0 )
    28922991       ENDIF
    28932992!
     
    28992998                           'input file ' // TRIM( input_file_dynamic ) //      &
    29002999                           TRIM( coupling_char )
    2901           CALL message( 'netcdf_data_input_mod', 'NDI010', 1, 2, 0, 6, 0 )
     3000          CALL message( 'netcdf_data_input_mod', 'PA0547', 1, 2, 0, 6, 0 )
    29023001       ENDIF
    29033002
     
    29403039                           'x- and/or y-direction ' //                         &
    29413040                           'do not match the respective model dimension'
    2942           CALL message( 'netcdf_data_input_mod', 'NDI011', 1, 2, 0, 6, 0 )
     3041          CALL message( 'netcdf_data_input_mod', 'PA0548', 1, 2, 0, 6, 0 )
    29433042       ENDIF
    29443043!
    29453044!--    Check if grid spacing of provided input data matches the respective
    2946 !--    grid spacing in the model.
    2947        IF ( dim_static%x(1) - dim_static%x(0) /= dx  .OR.                      &
    2948             dim_static%y(1) - dim_static%y(0) /= dy )  THEN
     3045!--    grid spacing in the model. 
     3046       IF ( ABS( dim_static%x(1) - dim_static%x(0) - dx ) > 10E-6_wp  .OR.     &
     3047            ABS( dim_static%y(1) - dim_static%y(0) - dy ) > 10E-6_wp )  THEN
    29493048          message_string = 'Static input file: horizontal grid spacing ' //    &
    29503049                           'in x- and/or y-direction ' //                      &
    29513050                           'do not match the respective model grid spacing.'
    2952           CALL message( 'netcdf_data_input_mod', 'NDI012', 1, 2, 0, 6, 0 )
     3051          CALL message( 'netcdf_data_input_mod', 'PA0549', 1, 2, 0, 6, 0 )
    29533052       ENDIF
    29543053!
     
    29603059          message_string = 'NetCDF variable zt is not ' //                     &
    29613060                           'allowed to have missing data'
    2962           CALL message( 'netcdf_data_input_mod', 'NDI013', 2, 2, myid, 6, 0 )
     3061          CALL message( 'netcdf_data_input_mod', 'PA0550', 2, 2, myid, 6, 0 )
    29633062       ENDIF
    29643063!
     
    29673066          message_string = 'NetCDF variable zt is not ' //                     &
    29683067                           'allowed to have negative values'
    2969           CALL message( 'netcdf_data_input_mod', 'NDI013', 2, 2, myid, 6, 0 )
     3068          CALL message( 'netcdf_data_input_mod', 'PA0551', 2, 2, myid, 6, 0 )
    29703069       ENDIF
    29713070!
     
    29773076                message_string = 'Reading 3D building data - too much ' //     &
    29783077                                 'data points along the vertical coordinate.'
    2979                 CALL message( 'netcdf_data_input_mod', 'NDI014', 2, 2, 0, 6, 0 )
     3078                CALL message( 'netcdf_data_input_mod', 'PA0552', 2, 2, 0, 6, 0 )
    29803079             ENDIF
    29813080
     
    29843083                message_string = 'Reading 3D building data - vertical ' //     &
    29853084                                 'coordinate do not match numeric grid.'
    2986                 CALL message( 'netcdf_data_input_mod', 'NDI015', 2, 2, 0, 6, 0 )
     3085                CALL message( 'netcdf_data_input_mod', 'PA0553', 2, 2, 0, 6, 0 )
    29873086             ENDIF
    29883087          ENDIF
     
    30073106                           'required. If urban-surface model is applied, ' //  &
    30083107                           'also building_type ist required'
    3009           CALL message( 'netcdf_data_input_mod', 'NDI016', 1, 2, 0, 6, 0 )
     3108          CALL message( 'netcdf_data_input_mod', 'PA0554', 1, 2, 0, 6, 0 )
    30103109       ENDIF
    30113110!
     
    30163115          IF ( ANY( vegetation_type_f%var == 0 ) )  THEN
    30173116             IF ( .NOT. vegetation_pars_f%from_file )  THEN
    3018                 message_string = 'If vegegation_type = 0 at any location, ' // &
     3117                message_string = 'If vegetation_type = 0 at any location, ' // &
    30193118                                 'vegetation_pars is required'
    3020                 CALL message( 'netcdf_data_input_mod', 'NDI017', 2, 2, -1, 6, 0 )
     3119                CALL message( 'netcdf_data_input_mod', 'PA0555', 2, 2, -1, 6, 0 )
    30213120             ENDIF
    30223121             IF ( .NOT. root_area_density_lsm_f%from_file )  THEN
    3023                 message_string = 'If vegegation_type = 0 at any location, ' // &
     3122                message_string = 'If vegetation_type = 0 at any location, ' // &
    30243123                                 'root_area_dens_s is required'
    3025                 CALL message( 'netcdf_data_input_mod', 'NDI018', 2, 2, myid, 6, 0 )
     3124                CALL message( 'netcdf_data_input_mod', 'PA0556', 2, 2, myid, 6, 0 )
    30263125             ENDIF
    30273126          ENDIF
     
    30433142             message_string = 'If soil_type = 0 at any location, ' //          &
    30443143                              'soil_pars is required'
    3045              CALL message( 'netcdf_data_input_mod', 'NDI019', 2, 2, myid, 6, 0 )
     3144             CALL message( 'netcdf_data_input_mod', 'PA0557', 2, 2, myid, 6, 0 )
    30463145          ENDIF
    30473146       ENDIF
     
    30533152                message_string = 'If building_type = 0 at any location, ' //   &
    30543153                                 'building_pars is required'
    3055                 CALL message( 'netcdf_data_input_mod', 'NDI020', 2, 2, myid, 6, 0 )
     3154                CALL message( 'netcdf_data_input_mod', 'PA0558', 2, 2, myid, 6, 0 )
    30563155             ENDIF
    30573156          ENDIF
     
    30643163                message_string = 'If albedo_type = 0 at any location, ' //     &
    30653164                                 'albedo_pars is required'
    3066                 CALL message( 'netcdf_data_input_mod', 'NDI021', 2, 2, myid, 6, 0 )
     3165                CALL message( 'netcdf_data_input_mod', 'PA0559', 2, 2, myid, 6, 0 )
    30673166             ENDIF
    30683167          ENDIF
     
    30753174                message_string = 'If pavement_type = 0 at any location, ' //   &
    30763175                                 'pavement_pars is required'
    3077                 CALL message( 'netcdf_data_input_mod', 'NDI022', 2, 2, myid, 6, 0 )
     3176                CALL message( 'netcdf_data_input_mod', 'PA0560', 2, 2, myid, 6, 0 )
    30783177             ENDIF
    30793178          ENDIF
     
    30873186                message_string = 'If pavement_type = 0 at any location, ' //   &
    30883187                                 'pavement_subsurface_pars is required'
    3089                 CALL message( 'netcdf_data_input_mod', 'NDI023', 2, 2, myid, 6, 0 )
     3188                CALL message( 'netcdf_data_input_mod', 'PA0561', 2, 2, myid, 6, 0 )
    30903189             ENDIF
    30913190          ENDIF
     
    30983197                message_string = 'If water_type = 0 at any location, ' //      &
    30993198                                 'water_pars is required'
    3100                 CALL message( 'netcdf_data_input_mod', 'NDI024', 2, 2,myid, 6, 0 )
     3199                CALL message( 'netcdf_data_input_mod', 'PA0562', 2, 2,myid, 6, 0 )
    31013200             ENDIF
    31023201          ENDIF
     
    31183217                                 'building_type, or water_type must be set '// &
    31193218                                 'to a non-missing value. Grid point: ', j, i
    3120                 CALL message( 'netcdf_data_input_mod', 'NDI025', 2, 2, myid, 6, 0 )
     3219                CALL message( 'netcdf_data_input_mod', 'PA0563', 2, 2, myid, 6, 0 )
    31213220             ENDIF
    31223221!
     
    31383237                                 'location (y,x) where vegetation_type or ' // &
    31393238                                 'pavement_type is a non-missing value.'
    3140                    CALL message( 'netcdf_data_input_mod', 'NDI026',            &
     3239                   CALL message( 'netcdf_data_input_mod', 'PA0564',            &
    31413240                                  2, 2, myid, 6, 0 )
    31423241                ENDIF
     
    31593258                                 'given at a location, surface_fraction ' //   &
    31603259                                 'must be provided.'
    3161                    CALL message( 'netcdf_data_input_mod', 'NDI027',            &
     3260                   CALL message( 'netcdf_data_input_mod', 'PA0565',            &
    31623261                                  2, 2, myid, 6, 0 )
    31633262                ELSEIF ( ANY ( surface_fraction_f%frac(:,j,i) ==               &
     
    31663265                                 'given at a location, surface_fraction ' //   &
    31673266                                 'must be provided.'
    3168                    CALL message( 'netcdf_data_input_mod', 'NDI027',            &
     3267                   CALL message( 'netcdf_data_input_mod', 'PA0565',            &
    31693268                                  2, 2, myid, 6, 0 )
    31703269                ENDIF
     
    31793278                IF ( SUM ( surface_fraction_f%frac(0:2,j,i) ) > 1.0_wp )  THEN
    31803279                   message_string = 'surface_fraction must not exceed 1'
    3181                    CALL message( 'netcdf_data_input_mod', 'NDI028',            &
     3280                   CALL message( 'netcdf_data_input_mod', 'PA0566',            &
    31823281                                  2, 2, myid, 6, 0 )
    31833282                ENDIF
     
    32053304                             'water surface is given at (i,j) = ( ', i, j,     &
    32063305                             ' ), but surface fraction is 0 for the given type.'
    3207                    CALL message( 'netcdf_data_input_mod', 'NDI029',            &
     3306                   CALL message( 'netcdf_data_input_mod', 'PA0567',            &
    32083307                                  2, 2, myid, 6, 0 )
    32093308                ENDIF
     
    32323331                             ' ), but surface fraction is not 0 for the ' //   &
    32333332                             'given type.'
    3234                    CALL message( 'netcdf_data_input_mod', 'NDI030',            &
     3333                   CALL message( 'netcdf_data_input_mod', 'PA0568',            &
    32353334                                  2, 2, myid, 6, 0 )
    32363335                ENDIF
     
    32473346                                       'parameters of vegetation_pars at '//   &
    32483347                                       'this location must be set.'
    3249                       CALL message( 'netcdf_data_input_mod', 'NDI031',         &
     3348                      CALL message( 'netcdf_data_input_mod', 'PA0569',         &
    32503349                                     2, 2, myid, 6, 0 )
    32513350                   ENDIF
     
    32623361                                       'levels of root_area_dens_s ' //        &
    32633362                                       'must be set at this location.'
    3264                       CALL message( 'netcdf_data_input_mod', 'NDI032',         &
     3363                      CALL message( 'netcdf_data_input_mod', 'PA0570',         &
    32653364                                     2, 2, myid, 6, 0 )
    32663365                   ENDIF
     
    32863385                   message_string = 'If soil_type(y,x) = 0, all levels of '  //&
    32873386                                    'soil_pars at this location must be set.'
    3288                    CALL message( 'netcdf_data_input_mod', 'NDI033',            &
     3387                   CALL message( 'netcdf_data_input_mod', 'PA0571',            &
    32893388                                  2, 2, myid, 6, 0 )
    32903389                ENDIF
     
    33013400                                       'parameters of building_pars at this '//&
    33023401                                       'location must be set.'
    3303                       CALL message( 'netcdf_data_input_mod', 'NDI034',         &
     3402                      CALL message( 'netcdf_data_input_mod', 'PA0572',         &
    33043403                                     2, 2, myid, 6, 0 )
    33053404                   ENDIF
     
    33183417                                         'urban-surface model is applied. ' // &
    33193418                                         'i, j = ', i, j
    3320                       CALL message( 'netcdf_data_input_mod', 'NDI035',         &
     3419                      CALL message( 'netcdf_data_input_mod', 'PA0573',         &
    33213420                                     2, 2, myid, 6, 0 )
    33223421                   ENDIF
     
    33303429                                         'urban-surface model is applied. ' // &
    33313430                                         'i, j = ', i, j
    3332                       CALL message( 'netcdf_data_input_mod', 'NDI035',         &
     3431                      CALL message( 'netcdf_data_input_mod', 'PA0573',         &
    33333432                                     2, 2, myid, 6, 0 )
    33343433                   ENDIF
     
    33453444                                         'building is set requires an ID ' //  &
    33463445                                         '( and vice versa ). i, j = ', i, j
    3347                       CALL message( 'netcdf_data_input_mod', 'NDI036',         &
     3446                      CALL message( 'netcdf_data_input_mod', 'PA0574',         &
    33483447                                     2, 2, myid, 6, 0 )
    33493448                   ENDIF
     
    33543453                                         'building is set requires an ID ' //  &
    33553454                                         '( and vice versa ). i, j = ', i, j
    3356                       CALL message( 'netcdf_data_input_mod', 'NDI036',         &
     3455                      CALL message( 'netcdf_data_input_mod', 'PA0574',         &
    33573456                                     2, 2, myid, 6, 0 )
    33583457                   ENDIF
     
    33683467                      WRITE( message_string, * ) 'Each building grid point '// &
    33693468                                                 'requires an ID.', i, j
    3370                       CALL message( 'netcdf_data_input_mod', 'NDI036',         &
     3469                      CALL message( 'netcdf_data_input_mod', 'PA0575',         &
    33713470                                     2, 2, myid, 6, 0 )
    33723471                   ENDIF
     
    33763475                      WRITE( message_string, * ) 'Each building grid point '// &
    33773476                                                 'requires an ID.', i, j
    3378                       CALL message( 'netcdf_data_input_mod', 'NDI036',         &
     3477                      CALL message( 'netcdf_data_input_mod', 'PA0575',         &
    33793478                                     2, 2, myid, 6, 0 )
    33803479                   ENDIF
     
    33913490                                       'parameters of albedo_pars at this ' // &
    33923491                                       'location must be set.'
    3393                       CALL message( 'netcdf_data_input_mod', 'NDI037',         &
     3492                      CALL message( 'netcdf_data_input_mod', 'PA0576',         &
    33943493                                     2, 2, myid, 6, 0 )
    33953494                   ENDIF
     
    34073506                                       'parameters of pavement_pars at this '//&
    34083507                                       'location must be set.'
    3409                       CALL message( 'netcdf_data_input_mod', 'NDI038',         &
     3508                      CALL message( 'netcdf_data_input_mod', 'PA0577',         &
    34103509                                     2, 2, myid, 6, 0 )
    34113510                   ENDIF
     
    34243523                                       'pavement_subsurface_pars at this '//   &
    34253524                                       'location must be set.'
    3426                       CALL message( 'netcdf_data_input_mod', 'NDI039',         &
     3525                      CALL message( 'netcdf_data_input_mod', 'PA0578',         &
    34273526                                     2, 2, myid, 6, 0 )
    34283527                   ENDIF
     
    34403539                                       'parameters of water_pars at this ' //  &
    34413540                                       'location must be set.'
    3442                       CALL message( 'netcdf_data_input_mod', 'NDI040',         &
     3541                      CALL message( 'netcdf_data_input_mod', 'PA0579',         &
    34433542                                     2, 2, myid, 6, 0 )
    34443543                   ENDIF
     
    41404239!--    required.
    41414240       IF ( collective_read )  THEN
     4241#if defined( __netcdf4_parallel )
    41424242          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
     4243#endif
    41434244       ENDIF
    41444245!
     
    42004301!--    required.
    42014302       IF ( collective_read )  THEN
     4303#if defined( __netcdf4_parallel )       
    42024304          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
     4305#endif
    42034306       ENDIF
    42044307!
     
    42604363!--    required.
    42614364       IF ( collective_read )  THEN
     4365#if defined( __netcdf4_parallel )       
    42624366          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
     4367#endif         
    42634368       ENDIF
    42644369!
     
    43264431!--    required.
    43274432       IF ( collective_read )  THEN
     4433#if defined( __netcdf4_parallel )
    43284434          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
     4435#endif         
    43294436       ENDIF
    43304437!
     
    43944501!--    required.
    43954502       IF ( collective_read )  THEN
     4503#if defined( __netcdf4_parallel )       
    43964504          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
     4505#endif
    43974506       ENDIF
    43984507!
     
    44664575! !--    required.
    44674576!        IF ( collective_read )  THEN
     4577! #if defined( __netcdf4_parallel )
    44684578!           nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
     4579! #endif
    44694580!        ENDIF
    44704581!
     
    45424653!--    required.
    45434654       IF ( collective_read )  THEN
     4655#if defined( __netcdf4_parallel )       
    45444656          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
     4657#endif
    45454658       ENDIF
    45464659!
     
    46324745!--    read operations are only enabled for top-boundary data.
    46334746       IF ( collective_read  .AND.  par_access )  THEN
     4747#if defined( __netcdf4_parallel )       
    46344748          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
     4749#endif
    46354750       ENDIF   
    46364751!
Note: See TracChangeset for help on using the changeset viewer.