Changeset 3737 for palm/trunk/SOURCE/netcdf_data_input_mod.f90
- Timestamp:
- Feb 12, 2019 4:57:06 PM (4 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/netcdf_data_input_mod.f90
r3705 r3737 25 25 ! ----------------- 26 26 ! $Id$ 27 ! Enable mesoscale offline nesting for chemistry variables as well as 28 ! initialization of chemistry via dynamic input file. 29 ! 30 ! 3705 2019-01-29 19:56:39Z suehring 27 31 ! Interface for attribute input of 8-bit and 32-bit integer 28 32 ! … … 310 314 TYPE nest_offl_type 311 315 312 CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE :: var_names 316 CHARACTER(LEN=16) :: char_l = 'ls_forcing_left_' !< leading substring for variables at left boundary 317 CHARACTER(LEN=17) :: char_n = 'ls_forcing_north_' !< leading substring for variables at north boundary 318 CHARACTER(LEN=17) :: char_r = 'ls_forcing_right_' !< leading substring for variables at right boundary 319 CHARACTER(LEN=17) :: char_s = 'ls_forcing_south_' !< leading substring for variables at south boundary 320 CHARACTER(LEN=15) :: char_t = 'ls_forcing_top_' !< leading substring for variables at top boundary 321 322 CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE :: var_names !< list of variable in dynamic input file 323 CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE :: var_names_chem_l !< names of mesoscale nested chemistry variables at left boundary 324 CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE :: var_names_chem_n !< names of mesoscale nested chemistry variables at north boundary 325 CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE :: var_names_chem_r !< names of mesoscale nested chemistry variables at right boundary 326 CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE :: var_names_chem_s !< names of mesoscale nested chemistry variables at south boundary 327 CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE :: var_names_chem_t !< names of mesoscale nested chemistry variables at top boundary 313 328 314 329 INTEGER(iwp) :: nt !< number of time levels in dynamic input file … … 319 334 320 335 LOGICAL :: init = .FALSE. !< flag indicating that offline nesting is already initialized 336 337 LOGICAL, DIMENSION(:), ALLOCATABLE :: chem_from_file_l !< flags inidicating whether left boundary data for chemistry is in dynamic input file 338 LOGICAL, DIMENSION(:), ALLOCATABLE :: chem_from_file_n !< flags inidicating whether north boundary data for chemistry is in dynamic input file 339 LOGICAL, DIMENSION(:), ALLOCATABLE :: chem_from_file_r !< flags inidicating whether right boundary data for chemistry is in dynamic input file 340 LOGICAL, DIMENSION(:), ALLOCATABLE :: chem_from_file_s !< flags inidicating whether south boundary data for chemistry is in dynamic input file 341 LOGICAL, DIMENSION(:), ALLOCATABLE :: chem_from_file_t !< flags inidicating whether top boundary data for chemistry is in dynamic input file 321 342 322 343 REAL(wp), DIMENSION(:), ALLOCATABLE :: surface_pressure !< time dependent surface pressure … … 357 378 REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: q_top !< mixing ratio at top boundary 358 379 REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: pt_top !< potentital temperautre at top boundary 380 381 REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE :: chem_left !< chemical species at left boundary 382 REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE :: chem_north !< chemical species at left boundary 383 REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE :: chem_right !< chemical species at left boundary 384 REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE :: chem_south !< chemical species at left boundary 385 REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE :: chem_top !< chemical species at left boundary 359 386 360 387 END TYPE nest_offl_type … … 362 389 TYPE init_type 363 390 391 CHARACTER(LEN=16) :: init_char = 'init_atmosphere_' !< leading substring for init variables 364 392 CHARACTER(LEN=23) :: origin_time = '2000-01-01 00:00:00 +00' !< reference time of input data 393 CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE :: var_names_chem !< list of chemistry variable names that can potentially be on file 365 394 366 395 INTEGER(iwp) :: lod_msoil !< level of detail - soil moisture … … 378 407 INTEGER(iwp) :: nzu !< number of vertical levels on scalar grid in dynamic input file 379 408 INTEGER(iwp) :: nzw !< number of vertical levels on w grid in dynamic input file 409 410 INTEGER(iwp), DIMENSION(:), ALLOCATABLE :: lod_chem !< level of detail - chemistry variables 380 411 381 412 LOGICAL :: from_file_msoil = .FALSE. !< flag indicating whether soil moisture is already initialized from file … … 388 419 LOGICAL :: from_file_vg = .FALSE. !< flag indicating whether ug is already initialized from file 389 420 LOGICAL :: from_file_w = .FALSE. !< flag indicating whether w is already initialized from file 421 422 LOGICAL, DIMENSION(:), ALLOCATABLE :: from_file_chem !< flag indicating whether chemistry variable is read from file 390 423 391 424 REAL(wp) :: fill_msoil !< fill value for soil moisture … … 403 436 REAL(wp) :: rotation_angle = 0.0_wp !< rotation angle of input data 404 437 438 REAL(wp), DIMENSION(:), ALLOCATABLE :: fill_chem !< fill value - chemistry variables 405 439 REAL(wp), DIMENSION(:), ALLOCATABLE :: msoil_1d !< initial vertical profile of soil moisture 406 440 REAL(wp), DIMENSION(:), ALLOCATABLE :: pt_init !< initial vertical profile of pt … … 415 449 REAL(wp), DIMENSION(:), ALLOCATABLE :: zu_atmos !< vertical levels at scalar grid in dynamic input file, used for interpolation 416 450 REAL(wp), DIMENSION(:), ALLOCATABLE :: zw_atmos !< vertical levels at w grid in dynamic input file, used for interpolation 451 452 REAL(wp), DIMENSION(:,:), ALLOCATABLE :: chem_init !< initial vertical profiles of chemistry variables 417 453 418 454 … … 727 763 CHARACTER(LEN=100) :: input_file_uvem = 'PIDS_UVEM' !< Name of file which comprises static uv_exposure model input data 728 764 CHARACTER(LEN=100) :: input_file_vm = 'PIDS_VM' !< Name of file which comprises virtual measurement data 729 730 CHARACTER 765 766 CHARACTER(LEN=25), ALLOCATABLE, DIMENSION(:) :: string_values !< output of string variables read from netcdf input files 731 767 732 768 INTEGER(iwp) :: id_emis !< NetCDF id of input file for chemistry emissions: TBD: It has to be removed … … 2713 2749 2714 2750 USE control_parameters, & 2715 ONLY: bc_lr_cyc, bc_ns_cyc, humidity, message_string, neutral 2751 ONLY: air_chemistry, bc_lr_cyc, bc_ns_cyc, humidity, & 2752 message_string, neutral 2716 2753 2717 2754 USE indices, & … … 2725 2762 2726 2763 INTEGER(iwp) :: id_dynamic !< NetCDF id of dynamic input file 2764 INTEGER(iwp) :: n !< running index for chemistry variables 2727 2765 INTEGER(iwp) :: num_vars !< number of variables in netcdf input file 2728 2766 … … 3078 3116 CALL message( 'netcdf_data_input_mod', 'PA0544', 1, 2, 0, 6, 0 ) 3079 3117 ENDIF 3118 ENDIF 3119 ! 3120 !-- Read chemistry variables. 3121 !-- Please note, for the moment, only LOD=1 is allowed 3122 IF ( air_chemistry ) THEN 3123 ! 3124 !-- Allocate chemistry input profiles, as well as arrays for fill values 3125 !-- and LOD's. 3126 ALLOCATE( init_3d%chem_init(nzb:nzt+1, & 3127 1:UBOUND(init_3d%var_names_chem, 1 )) ) 3128 ALLOCATE( init_3d%fill_chem(1:UBOUND(init_3d%var_names_chem, 1)) ) 3129 ALLOCATE( init_3d%lod_chem(1:UBOUND(init_3d%var_names_chem, 1)) ) 3130 3131 DO n = 1, UBOUND(init_3d%var_names_chem, 1) 3132 IF ( check_existence( var_names, & 3133 TRIM( init_3d%var_names_chem(n) ) ) ) THEN 3134 ! 3135 !-- Read attributes for the fill value and level-of-detail 3136 CALL get_attribute( id_dynamic, char_fill, & 3137 init_3d%fill_chem(n), & 3138 .FALSE., & 3139 TRIM( init_3d%var_names_chem(n) ) ) 3140 CALL get_attribute( id_dynamic, char_lod, & 3141 init_3d%lod_chem(n), & 3142 .FALSE., & 3143 TRIM( init_3d%var_names_chem(n) ) ) 3144 ! 3145 !-- Give message that only LOD=1 is allowed. 3146 IF ( init_3d%lod_chem(n) /= 1 ) THEN 3147 message_string = 'For chemistry variables only LOD=1 is ' //& 3148 'allowed.' 3149 CALL message( 'netcdf_data_input_mod', 'PA0586', & 3150 1, 2, 0, 6, 0 ) 3151 ENDIF 3152 ! 3153 !-- level-of-detail 1 - read initialization profile 3154 CALL get_variable( id_dynamic, & 3155 TRIM( init_3d%var_names_chem(n) ), & 3156 init_3d%chem_init(nzb+1:nzt,n) ) 3157 ! 3158 !-- Set bottom and top boundary condition (Neumann) 3159 init_3d%chem_init(nzb,n) = init_3d%chem_init(nzb+1,n) 3160 init_3d%chem_init(nzt+1,n) = init_3d%chem_init(nzt,n) 3161 3162 init_3d%from_file_chem(n) = .TRUE. 3163 ENDIF 3164 ENDDO 3080 3165 ENDIF 3081 3166 ! … … 3326 3411 3327 3412 USE control_parameters, & 3328 ONLY: bc_dirichlet_l, bc_dirichlet_n, bc_dirichlet_r,&3329 bc_dirichlet_ s, humidity, neutral, nesting_offline,&3330 time_since_reference_point3413 ONLY: air_chemistry, bc_dirichlet_l, bc_dirichlet_n, & 3414 bc_dirichlet_r, bc_dirichlet_s, humidity, neutral, & 3415 nesting_offline, time_since_reference_point 3331 3416 3332 3417 USE indices, & … … 3336 3421 3337 3422 INTEGER(iwp) :: id_dynamic !< NetCDF id of dynamic input file 3423 INTEGER(iwp) :: n !< running index for chemistry variables 3338 3424 INTEGER(iwp) :: num_vars !< number of variables in netcdf input file 3339 3425 INTEGER(iwp) :: t !< running index time dimension … … 3454 3540 nys+1, nzb+1, nest_offl%tind+1, & 3455 3541 nyn-nys+1, nest_offl%nzu, 2, .FALSE. ) 3542 ENDIF 3543 3544 IF ( air_chemistry ) THEN 3545 DO n = 1, UBOUND(nest_offl%var_names_chem_l, 1) 3546 IF ( check_existence( nest_offl%var_names, & 3547 nest_offl%var_names_chem_l(n) ) ) & 3548 THEN 3549 CALL get_variable( id_dynamic, & 3550 TRIM( nest_offl%var_names_chem_l(n) ), & 3551 nest_offl%chem_left(0:1,nzb+1:nzt,nys:nyn,n), & 3552 nys+1, nzb+1, nest_offl%tind+1, & 3553 nyn-nys+1, nest_offl%nzu, 2, .FALSE. ) 3554 nest_offl%chem_from_file_l(n) = .TRUE. 3555 ENDIF 3556 ENDDO 3456 3557 ENDIF 3457 3558 … … 3485 3586 nys+1, nzb+1, nest_offl%tind+1, & 3486 3587 nyn-nys+1, nest_offl%nzu, 2, .FALSE. ) 3588 ENDIF 3589 3590 IF ( air_chemistry ) THEN 3591 DO n = 1, UBOUND(nest_offl%var_names_chem_r, 1) 3592 IF ( check_existence( nest_offl%var_names, & 3593 nest_offl%var_names_chem_r(n) ) ) & 3594 THEN 3595 CALL get_variable( id_dynamic, & 3596 TRIM( nest_offl%var_names_chem_r(n) ), & 3597 nest_offl%chem_right(0:1,nzb+1:nzt,nys:nyn,n), & 3598 nys+1, nzb+1, nest_offl%tind+1, & 3599 nyn-nys+1, nest_offl%nzu, 2, .FALSE. ) 3600 nest_offl%chem_from_file_r(n) = .TRUE. 3601 ENDIF 3602 ENDDO 3487 3603 ENDIF 3488 3604 ENDIF … … 3517 3633 nxr-nxl+1, nest_offl%nzu, 2, .FALSE. ) 3518 3634 ENDIF 3635 3636 IF ( air_chemistry ) THEN 3637 DO n = 1, UBOUND(nest_offl%var_names_chem_n, 1) 3638 IF ( check_existence( nest_offl%var_names, & 3639 nest_offl%var_names_chem_n(n) ) ) & 3640 THEN 3641 CALL get_variable( id_dynamic, & 3642 TRIM( nest_offl%var_names_chem_n(n) ), & 3643 nest_offl%chem_north(0:1,nzb+1:nzt,nxl:nxr,n), & 3644 nxl+1, nzb+1, nest_offl%tind+1, & 3645 nxr-nxl+1, nest_offl%nzu, 2, .FALSE. ) 3646 nest_offl%chem_from_file_n(n) = .TRUE. 3647 ENDIF 3648 ENDDO 3649 ENDIF 3519 3650 ENDIF 3520 3651 … … 3547 3678 nxr-nxl+1, nest_offl%nzu, 2, .FALSE. ) 3548 3679 ENDIF 3680 3681 IF ( air_chemistry ) THEN 3682 DO n = 1, UBOUND(nest_offl%var_names_chem_s, 1) 3683 IF ( check_existence( nest_offl%var_names, & 3684 nest_offl%var_names_chem_s(n) ) ) & 3685 THEN 3686 CALL get_variable( id_dynamic, & 3687 TRIM( nest_offl%var_names_chem_s(n) ), & 3688 nest_offl%chem_south(0:1,nzb+1:nzt,nxl:nxr,n), & 3689 nxl+1, nzb+1, nest_offl%tind+1, & 3690 nxr-nxl+1, nest_offl%nzu, 2, .FALSE. ) 3691 nest_offl%chem_from_file_s(n) = .TRUE. 3692 ENDIF 3693 ENDDO 3694 ENDIF 3549 3695 ENDIF 3550 3696 … … 3577 3723 nxl+1, nys+1, nest_offl%tind+1, & 3578 3724 nxr-nxl+1, nyn-nys+1, 2, .TRUE. ) 3725 ENDIF 3726 3727 IF ( air_chemistry ) THEN 3728 DO n = 1, UBOUND(nest_offl%var_names_chem_t, 1) 3729 IF ( check_existence( nest_offl%var_names, & 3730 nest_offl%var_names_chem_t(n) ) ) THEN 3731 CALL get_variable( id_dynamic, & 3732 TRIM( nest_offl%var_names_chem_t(n) ), & 3733 nest_offl%chem_top(0:1,nys:nyn,nxl:nxr,n), & 3734 nxl+1, nys+1, nest_offl%tind+1, & 3735 nxr-nxl+1, nyn-nys+1, 2, .TRUE. ) 3736 nest_offl%chem_from_file_t(n) = .TRUE. 3737 ENDIF 3738 ENDDO 3579 3739 ENDIF 3580 3740
Note: See TracChangeset
for help on using the changeset viewer.