Changeset 2768 for palm/trunk/SOURCE
- Timestamp:
- Jan 24, 2018 3:38:29 PM (7 years ago)
- Location:
- palm/trunk/SOURCE
- Files:
-
- 2 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/chemistry_model_mod.f90
r2766 r2768 27 27 ! ----------------- 28 28 ! $Id$ 29 ! Shorten lines to maximum length of 132 characters 30 ! 31 ! 2766 2018-01-22 17:17:47Z kanani 29 32 ! Removed preprocessor directive __chem 30 33 ! … … 813 816 814 817 IF(myid == 0) THEN 815 WRITE(6,'(a,3x,a,3x,a,e12.4)') ' Species: ',chem_species(lsp)%name(1:7),' Initial Value = ',chem_species(lsp)%conc(nzb,nysg,nxlg) 818 WRITE(6,'(a,3x,a,3x,a,e12.4)') ' Species: ',chem_species(lsp)%name(1:7),' & 819 Initial Value = ',chem_species(lsp)%conc(nzb,nysg,nxlg) 816 820 ENDIF 817 821 ENDDO … … 1237 1241 DO lsp=1,nspec 1238 1242 IF (TRIM(spec_name) == TRIM(chem_species(lsp)%name)) THEN 1239 IF(myid == 0 .AND. chem_debug0 ) WRITE(6,*) 'Output of species ',TRIM(variable),' ',TRIM(chem_species(lsp)%name) 1243 IF(myid == 0 .AND. chem_debug0 ) WRITE(6,*) 'Output of species ',TRIM(variable),' & 1244 ',TRIM(chem_species(lsp)%name) 1240 1245 1241 1246 IF (av == 0) THEN … … 1507 1512 !------------------------------------------------------------------------------! 1508 1513 1509 SUBROUTINE chem_tendency ( cs_scalar_p, cs_scalar, tcs_scalar_m, pr_init_cs, i, j, i_omp_start, tn, ilsp, flux_s_cs, diss_s_cs, flux_l_cs, diss_l_cs ) 1514 SUBROUTINE chem_tendency ( cs_scalar_p, cs_scalar, tcs_scalar_m, pr_init_cs, & 1515 i, j, i_omp_start, tn, ilsp, flux_s_cs, diss_s_cs, & 1516 flux_l_cs, diss_l_cs ) 1510 1517 USE pegrid 1511 1518 USE advec_ws, ONLY: advec_s_ws … … 1514 1521 USE diffusion_s_mod, ONLY: diffusion_s 1515 1522 USE indices, ONLY: wall_flags_0 1516 USE surface_mod, & 1517 ONLY : surf_def_h, surf_def_v, surf_lsm_h, surf_lsm_v, surf_usm_h, & 1518 surf_usm_v 1523 USE surface_mod, ONLY: surf_def_h, surf_def_v, surf_lsm_h, surf_lsm_v, surf_usm_h, & 1524 surf_usm_v 1519 1525 !> Only one chem_spcs recieved prog_eqns at time. 1520 1526 !> cem_tendency is called in prog_eqns over loop => nvar … … 1522 1528 IMPLICIT NONE 1523 1529 1524 REAL(wp), DIMENSION(:,:,:), POINTER 1530 REAL(wp), DIMENSION(:,:,:), POINTER :: cs_scalar_p, cs_scalar, tcs_scalar_m 1525 1531 1526 1532 INTEGER(iwp),INTENT(IN) :: i, j, i_omp_start, tn, ilsp -
palm/trunk/SOURCE/plant_canopy_model_mod.f90
r2766 r2768 25 25 ! ----------------- 26 26 ! $Id$ 27 ! Added check for output quantity pcm_heatrate, some formatting 28 ! 29 ! 2766 2018-01-22 17:17:47Z kanani 27 30 ! Increased LEN of canopy mode to 30 28 31 ! … … 194 197 REAL(wp) :: leaf_scalar_exch_coeff = 0.0_wp !< canopy scalar exchange coeff. 195 198 REAL(wp) :: leaf_surface_conc = 0.0_wp !< leaf surface concentration 199 REAL(wp) :: lsc = 0.0_wp !< leaf surface concentration 196 200 REAL(wp) :: lsec = 0.0_wp !< leaf scalar exchange coeff. 197 REAL(wp) :: lsc = 0.0_wp !< leaf surface concentration198 201 REAL(wp) :: prototype_lad !< prototype leaf area density for computing effective optical depth 199 202 … … 204 207 REAL(wp), DIMENSION(:), ALLOCATABLE :: pre_lad !< preliminary lad 205 208 206 REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: & 207 pc_heating_rate !< plant canopy heating rate 208 REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: cum_lai_hf !< cumulative lai for heatflux calc. 209 REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: lad_s !< lad on scalar-grid 210 209 REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: cum_lai_hf !< cumulative lai for heatflux calc. 210 REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: lad_s !< lad on scalar-grid 211 REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: pc_heating_rate !< plant canopy heating rate 211 212 212 213 SAVE … … 287 288 288 289 CASE ( 'pcm_heatrate' ) 290 IF ( cthf == 0.0_wp ) THEN 291 message_string = 'output of "' // TRIM( var ) // '" requi' // & 292 'res setting of parameter cthf /= 0.0' 293 CALL message( 'pcm_check_data_output', 'PA1000', 1, 2, 0, 6, 0 ) 294 ENDIF 289 295 unit = 'K s-1' 290 296 … … 323 329 message_string = 'plant_canopy = .TRUE. requires a non-zero drag '// & 324 330 'coefficient & given value is canopy_drag_coeff = 0.0' 325 CALL message( ' check_parameters', 'PA0041', 1, 2, 0, 6, 0 )331 CALL message( 'pcm_check_parameters', 'PA0041', 1, 2, 0, 6, 0 ) 326 332 ENDIF 327 333 … … 331 337 'of the leaf area density profile requires ' // & 332 338 'both alpha_lad and beta_lad to be /= 9999999.9' 333 CALL message( ' check_parameters', 'PA0118', 1, 2, 0, 6, 0 )339 CALL message( 'pcm_check_parameters', 'PA0118', 1, 2, 0, 6, 0 ) 334 340 ENDIF 335 341 … … 339 345 'a non-zero lai_beta, but given value is ' // & 340 346 'lai_beta = 0.0' 341 CALL message( ' check_parameters', 'PA0119', 1, 2, 0, 6, 0 )347 CALL message( 'pcm_check_parameters', 'PA0119', 1, 2, 0, 6, 0 ) 342 348 ENDIF 343 349 … … 349 355 'function for the construction of the leaf area '// & 350 356 'density profile' 351 CALL message( ' check_parameters', 'PA0120', 1, 2, 0, 6, 0 )357 CALL message( 'pcm_check_parameters', 'PA0120', 1, 2, 0, 6, 0 ) 352 358 ENDIF 353 359 … … 355 361 message_string = 'plant_canopy = .TRUE. requires cloud_scheme /=' // & 356 362 ' seifert_beheng' 357 CALL message( ' check_parameters', 'PA0360', 1, 2, 0, 6, 0 )363 CALL message( 'pcm_check_parameters', 'PA0360', 1, 2, 0, 6, 0 ) 358 364 ENDIF 359 365 ! … … 365 371 TRIM( coupling_char ) // ' requires ' // & 366 372 'canopy_mode = read_from_file_3d' 367 CALL message( ' check_parameters', 'PA0999', 1, 2, 0, 6, 0 )373 CALL message( 'pcm_check_parameters', 'PA0999', 1, 2, 0, 6, 0 ) 368 374 ENDIF 369 375 … … 844 850 !-- When using the urban surface model (USM), canopy heating (pc_heating_rate) 845 851 !-- by radiation is calculated in the USM. 846 IF ( cthf /= 0.0_wp .AND. .NOT. urban_surface ) THEN852 IF ( cthf /= 0.0_wp .AND. .NOT. urban_surface ) THEN 847 853 848 854 ALLOCATE( cum_lai_hf(nzb:nzt+1,nysg:nyng,nxlg:nxrg), &
Note: See TracChangeset
for help on using the changeset viewer.