Changeset 3209 for palm/trunk/SOURCE/netcdf_data_input_mod.f90
- Timestamp:
- Aug 27, 2018 4:58:37 PM (6 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/netcdf_data_input_mod.f90
r3186 r3209 20 20 ! Current revisions: 21 21 ! ----------------- 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 23 29 ! 24 30 ! Former revisions: … … 303 309 REAL(wp) :: rotation_angle !< rotation angle of input data 304 310 305 REAL(wp), DIMENSION(:), ALLOCATABLE :: msoil_ init!< initial vertical profile of soil moisture311 REAL(wp), DIMENSION(:), ALLOCATABLE :: msoil_1d !< initial vertical profile of soil moisture 306 312 REAL(wp), DIMENSION(:), ALLOCATABLE :: pt_init !< initial vertical profile of pt 307 313 REAL(wp), DIMENSION(:), ALLOCATABLE :: q_init !< initial vertical profile of q 308 REAL(wp), DIMENSION(:), ALLOCATABLE :: tsoil_ init!< initial vertical profile of soil temperature314 REAL(wp), DIMENSION(:), ALLOCATABLE :: tsoil_1d !< initial vertical profile of soil temperature 309 315 REAL(wp), DIMENSION(:), ALLOCATABLE :: u_init !< initial vertical profile of u 310 316 REAL(wp), DIMENSION(:), ALLOCATABLE :: ug_init !< initial vertical profile of ug … … 317 323 318 324 319 REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: msoil 320 REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: tsoil 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 321 327 322 328 END TYPE init_type … … 573 579 MODULE PROCEDURE netcdf_data_input_init_3d 574 580 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 575 585 576 586 INTERFACE netcdf_data_input_lsf … … 595 605 MODULE PROCEDURE get_variable_3d_real 596 606 MODULE PROCEDURE get_variable_3d_real_dynamic 597 ! MODULE PROCEDURE get_variable_3d_real_v598 607 MODULE PROCEDURE get_variable_4d_real 599 608 END INTERFACE get_variable … … 626 635 PUBLIC netcdf_data_input_check_dynamic, netcdf_data_input_check_static, & 627 636 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, & 629 639 netcdf_data_input_interpolate, netcdf_data_input_lsf, & 630 640 netcdf_data_input_surface_data, netcdf_data_input_topo … … 1864 1874 '(level of detail) is not set ' // & 1865 1875 'properly for buildings_2d.' 1866 CALL message( 'netcdf_data_input_mod', ' NDI000', &1876 CALL message( 'netcdf_data_input_mod', 'PA0540', & 1867 1877 1, 2, 0, 6, 0 ) 1868 1878 ENDIF … … 1897 1907 '(level of detail) is not set ' // & 1898 1908 'properly for buildings_3d.' 1899 CALL message( 'netcdf_data_input_mod', ' NDI001', &1909 CALL message( 'netcdf_data_input_mod', 'PA0541', & 1900 1910 1, 2, 0, 6, 0 ) 1901 1911 ENDIF … … 1999 2009 message_string = 'If building heigths are prescribed in ' // & 2000 2010 '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 ) 2002 2012 ENDIF 2003 2013 ENDIF … … 2120 2130 CALL inquire_variable_names( id_dynamic, var_names ) 2121 2131 ! 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. 2125 2133 CALL get_dimension_length( id_dynamic, init_3d%nzu, 'z' ) 2126 2134 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' )2129 2135 ! 2130 2136 !-- Read also the horizontal dimensions. These are used just used fo … … 2146 2152 'does not match the number of numeric grid '// & 2147 2153 '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 ) 2149 2155 ENDIF 2150 2156 … … 2153 2159 'does not match the number of numeric grid '// & 2154 2160 '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 ) 2156 2162 ENDIF 2157 2163 ! … … 2165 2171 ALLOCATE( init_3d%zw_atmos(1:init_3d%nzw) ) 2166 2172 CALL get_variable( id_dynamic, 'zw', init_3d%zw_atmos ) 2167 ENDIF2168 IF ( check_existence( var_names, 'zsoil' ) ) THEN2169 ALLOCATE( init_3d%z_soil(1:init_3d%nzs) )2170 CALL get_variable( id_dynamic, 'zsoil', init_3d%z_soil )2171 2173 ENDIF 2172 2174 ! … … 2184 2186 message_string = 'Vertical grid in dynamic driver does not '// & 2185 2187 '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 ) 2187 2189 ENDIF 2188 2190 ! … … 2264 2266 ENDIF 2265 2267 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 ) 2266 2271 ENDIF 2267 2272 ! … … 2307 2312 ENDIF 2308 2313 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 ) 2309 2317 ENDIF 2310 2318 ! … … 2345 2353 ENDIF 2346 2354 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 ) 2347 2358 ENDIF 2348 2359 ! … … 2385 2396 ENDIF 2386 2397 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 ) 2387 2402 ENDIF 2388 2403 ENDIF … … 2425 2440 ENDIF 2426 2441 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 ) 2490 2446 ENDIF 2491 2447 ENDIF … … 2512 2468 message_string = 'NetCDF input for init_atmosphere_u must ' // & 2513 2469 '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 ) 2515 2471 ENDIF 2516 2472 ENDIF … … 2528 2484 message_string = 'NetCDF input for init_atmosphere_v must ' // & 2529 2485 '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 ) 2531 2487 ENDIF 2532 2488 ENDIF … … 2544 2500 message_string = 'NetCDF input for init_atmosphere_w must ' // & 2545 2501 '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 ) 2547 2503 ENDIF 2548 2504 ENDIF … … 2560 2516 message_string = 'NetCDF input for init_atmosphere_pt must ' // & 2561 2517 '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 ) 2563 2519 ENDIF 2564 2520 ENDIF … … 2576 2532 message_string = 'NetCDF input for init_atmosphere_q must ' // & 2577 2533 '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 ) 2579 2535 ENDIF 2580 2536 ENDIF … … 2585 2541 2586 2542 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 2587 2686 2588 2687 !------------------------------------------------------------------------------! … … 2889 2988 'input file ' // & 2890 2989 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 ) 2892 2991 ENDIF 2893 2992 ! … … 2899 2998 'input file ' // TRIM( input_file_dynamic ) // & 2900 2999 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 ) 2902 3001 ENDIF 2903 3002 … … 2940 3039 'x- and/or y-direction ' // & 2941 3040 '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 ) 2943 3042 ENDIF 2944 3043 ! 2945 3044 !-- 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) THEN3045 !-- 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 2949 3048 message_string = 'Static input file: horizontal grid spacing ' // & 2950 3049 'in x- and/or y-direction ' // & 2951 3050 '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 ) 2953 3052 ENDIF 2954 3053 ! … … 2960 3059 message_string = 'NetCDF variable zt is not ' // & 2961 3060 '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 ) 2963 3062 ENDIF 2964 3063 ! … … 2967 3066 message_string = 'NetCDF variable zt is not ' // & 2968 3067 '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 ) 2970 3069 ENDIF 2971 3070 ! … … 2977 3076 message_string = 'Reading 3D building data - too much ' // & 2978 3077 '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 ) 2980 3079 ENDIF 2981 3080 … … 2984 3083 message_string = 'Reading 3D building data - vertical ' // & 2985 3084 '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 ) 2987 3086 ENDIF 2988 3087 ENDIF … … 3007 3106 'required. If urban-surface model is applied, ' // & 3008 3107 '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 ) 3010 3109 ENDIF 3011 3110 ! … … 3016 3115 IF ( ANY( vegetation_type_f%var == 0 ) ) THEN 3017 3116 IF ( .NOT. vegetation_pars_f%from_file ) THEN 3018 message_string = 'If vege gation_type = 0 at any location, ' // &3117 message_string = 'If vegetation_type = 0 at any location, ' // & 3019 3118 '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 ) 3021 3120 ENDIF 3022 3121 IF ( .NOT. root_area_density_lsm_f%from_file ) THEN 3023 message_string = 'If vege gation_type = 0 at any location, ' // &3122 message_string = 'If vegetation_type = 0 at any location, ' // & 3024 3123 '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 ) 3026 3125 ENDIF 3027 3126 ENDIF … … 3043 3142 message_string = 'If soil_type = 0 at any location, ' // & 3044 3143 '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 ) 3046 3145 ENDIF 3047 3146 ENDIF … … 3053 3152 message_string = 'If building_type = 0 at any location, ' // & 3054 3153 '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 ) 3056 3155 ENDIF 3057 3156 ENDIF … … 3064 3163 message_string = 'If albedo_type = 0 at any location, ' // & 3065 3164 '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 ) 3067 3166 ENDIF 3068 3167 ENDIF … … 3075 3174 message_string = 'If pavement_type = 0 at any location, ' // & 3076 3175 '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 ) 3078 3177 ENDIF 3079 3178 ENDIF … … 3087 3186 message_string = 'If pavement_type = 0 at any location, ' // & 3088 3187 '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 ) 3090 3189 ENDIF 3091 3190 ENDIF … … 3098 3197 message_string = 'If water_type = 0 at any location, ' // & 3099 3198 '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 ) 3101 3200 ENDIF 3102 3201 ENDIF … … 3118 3217 'building_type, or water_type must be set '// & 3119 3218 '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 ) 3121 3220 ENDIF 3122 3221 ! … … 3138 3237 'location (y,x) where vegetation_type or ' // & 3139 3238 'pavement_type is a non-missing value.' 3140 CALL message( 'netcdf_data_input_mod', ' NDI026', &3239 CALL message( 'netcdf_data_input_mod', 'PA0564', & 3141 3240 2, 2, myid, 6, 0 ) 3142 3241 ENDIF … … 3159 3258 'given at a location, surface_fraction ' // & 3160 3259 'must be provided.' 3161 CALL message( 'netcdf_data_input_mod', ' NDI027', &3260 CALL message( 'netcdf_data_input_mod', 'PA0565', & 3162 3261 2, 2, myid, 6, 0 ) 3163 3262 ELSEIF ( ANY ( surface_fraction_f%frac(:,j,i) == & … … 3166 3265 'given at a location, surface_fraction ' // & 3167 3266 'must be provided.' 3168 CALL message( 'netcdf_data_input_mod', ' NDI027', &3267 CALL message( 'netcdf_data_input_mod', 'PA0565', & 3169 3268 2, 2, myid, 6, 0 ) 3170 3269 ENDIF … … 3179 3278 IF ( SUM ( surface_fraction_f%frac(0:2,j,i) ) > 1.0_wp ) THEN 3180 3279 message_string = 'surface_fraction must not exceed 1' 3181 CALL message( 'netcdf_data_input_mod', ' NDI028', &3280 CALL message( 'netcdf_data_input_mod', 'PA0566', & 3182 3281 2, 2, myid, 6, 0 ) 3183 3282 ENDIF … … 3205 3304 'water surface is given at (i,j) = ( ', i, j, & 3206 3305 ' ), 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', & 3208 3307 2, 2, myid, 6, 0 ) 3209 3308 ENDIF … … 3232 3331 ' ), but surface fraction is not 0 for the ' // & 3233 3332 'given type.' 3234 CALL message( 'netcdf_data_input_mod', ' NDI030', &3333 CALL message( 'netcdf_data_input_mod', 'PA0568', & 3235 3334 2, 2, myid, 6, 0 ) 3236 3335 ENDIF … … 3247 3346 'parameters of vegetation_pars at '// & 3248 3347 'this location must be set.' 3249 CALL message( 'netcdf_data_input_mod', ' NDI031', &3348 CALL message( 'netcdf_data_input_mod', 'PA0569', & 3250 3349 2, 2, myid, 6, 0 ) 3251 3350 ENDIF … … 3262 3361 'levels of root_area_dens_s ' // & 3263 3362 'must be set at this location.' 3264 CALL message( 'netcdf_data_input_mod', ' NDI032', &3363 CALL message( 'netcdf_data_input_mod', 'PA0570', & 3265 3364 2, 2, myid, 6, 0 ) 3266 3365 ENDIF … … 3286 3385 message_string = 'If soil_type(y,x) = 0, all levels of ' //& 3287 3386 'soil_pars at this location must be set.' 3288 CALL message( 'netcdf_data_input_mod', ' NDI033', &3387 CALL message( 'netcdf_data_input_mod', 'PA0571', & 3289 3388 2, 2, myid, 6, 0 ) 3290 3389 ENDIF … … 3301 3400 'parameters of building_pars at this '//& 3302 3401 'location must be set.' 3303 CALL message( 'netcdf_data_input_mod', ' NDI034', &3402 CALL message( 'netcdf_data_input_mod', 'PA0572', & 3304 3403 2, 2, myid, 6, 0 ) 3305 3404 ENDIF … … 3318 3417 'urban-surface model is applied. ' // & 3319 3418 'i, j = ', i, j 3320 CALL message( 'netcdf_data_input_mod', ' NDI035', &3419 CALL message( 'netcdf_data_input_mod', 'PA0573', & 3321 3420 2, 2, myid, 6, 0 ) 3322 3421 ENDIF … … 3330 3429 'urban-surface model is applied. ' // & 3331 3430 'i, j = ', i, j 3332 CALL message( 'netcdf_data_input_mod', ' NDI035', &3431 CALL message( 'netcdf_data_input_mod', 'PA0573', & 3333 3432 2, 2, myid, 6, 0 ) 3334 3433 ENDIF … … 3345 3444 'building is set requires an ID ' // & 3346 3445 '( and vice versa ). i, j = ', i, j 3347 CALL message( 'netcdf_data_input_mod', ' NDI036', &3446 CALL message( 'netcdf_data_input_mod', 'PA0574', & 3348 3447 2, 2, myid, 6, 0 ) 3349 3448 ENDIF … … 3354 3453 'building is set requires an ID ' // & 3355 3454 '( and vice versa ). i, j = ', i, j 3356 CALL message( 'netcdf_data_input_mod', ' NDI036', &3455 CALL message( 'netcdf_data_input_mod', 'PA0574', & 3357 3456 2, 2, myid, 6, 0 ) 3358 3457 ENDIF … … 3368 3467 WRITE( message_string, * ) 'Each building grid point '// & 3369 3468 'requires an ID.', i, j 3370 CALL message( 'netcdf_data_input_mod', ' NDI036', &3469 CALL message( 'netcdf_data_input_mod', 'PA0575', & 3371 3470 2, 2, myid, 6, 0 ) 3372 3471 ENDIF … … 3376 3475 WRITE( message_string, * ) 'Each building grid point '// & 3377 3476 'requires an ID.', i, j 3378 CALL message( 'netcdf_data_input_mod', ' NDI036', &3477 CALL message( 'netcdf_data_input_mod', 'PA0575', & 3379 3478 2, 2, myid, 6, 0 ) 3380 3479 ENDIF … … 3391 3490 'parameters of albedo_pars at this ' // & 3392 3491 'location must be set.' 3393 CALL message( 'netcdf_data_input_mod', ' NDI037', &3492 CALL message( 'netcdf_data_input_mod', 'PA0576', & 3394 3493 2, 2, myid, 6, 0 ) 3395 3494 ENDIF … … 3407 3506 'parameters of pavement_pars at this '//& 3408 3507 'location must be set.' 3409 CALL message( 'netcdf_data_input_mod', ' NDI038', &3508 CALL message( 'netcdf_data_input_mod', 'PA0577', & 3410 3509 2, 2, myid, 6, 0 ) 3411 3510 ENDIF … … 3424 3523 'pavement_subsurface_pars at this '// & 3425 3524 'location must be set.' 3426 CALL message( 'netcdf_data_input_mod', ' NDI039', &3525 CALL message( 'netcdf_data_input_mod', 'PA0578', & 3427 3526 2, 2, myid, 6, 0 ) 3428 3527 ENDIF … … 3440 3539 'parameters of water_pars at this ' // & 3441 3540 'location must be set.' 3442 CALL message( 'netcdf_data_input_mod', ' NDI040', &3541 CALL message( 'netcdf_data_input_mod', 'PA0579', & 3443 3542 2, 2, myid, 6, 0 ) 3444 3543 ENDIF … … 4140 4239 !-- required. 4141 4240 IF ( collective_read ) THEN 4241 #if defined( __netcdf4_parallel ) 4142 4242 nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE) 4243 #endif 4143 4244 ENDIF 4144 4245 ! … … 4200 4301 !-- required. 4201 4302 IF ( collective_read ) THEN 4303 #if defined( __netcdf4_parallel ) 4202 4304 nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE) 4305 #endif 4203 4306 ENDIF 4204 4307 ! … … 4260 4363 !-- required. 4261 4364 IF ( collective_read ) THEN 4365 #if defined( __netcdf4_parallel ) 4262 4366 nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE) 4367 #endif 4263 4368 ENDIF 4264 4369 ! … … 4326 4431 !-- required. 4327 4432 IF ( collective_read ) THEN 4433 #if defined( __netcdf4_parallel ) 4328 4434 nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE) 4435 #endif 4329 4436 ENDIF 4330 4437 ! … … 4394 4501 !-- required. 4395 4502 IF ( collective_read ) THEN 4503 #if defined( __netcdf4_parallel ) 4396 4504 nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE) 4505 #endif 4397 4506 ENDIF 4398 4507 ! … … 4466 4575 ! !-- required. 4467 4576 ! IF ( collective_read ) THEN 4577 ! #if defined( __netcdf4_parallel ) 4468 4578 ! nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE) 4579 ! #endif 4469 4580 ! ENDIF 4470 4581 ! … … 4542 4653 !-- required. 4543 4654 IF ( collective_read ) THEN 4655 #if defined( __netcdf4_parallel ) 4544 4656 nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE) 4657 #endif 4545 4658 ENDIF 4546 4659 ! … … 4632 4745 !-- read operations are only enabled for top-boundary data. 4633 4746 IF ( collective_read .AND. par_access ) THEN 4747 #if defined( __netcdf4_parallel ) 4634 4748 nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE) 4749 #endif 4635 4750 ENDIF 4636 4751 !
Note: See TracChangeset
for help on using the changeset viewer.