- Timestamp:
- May 9, 2018 8:42:38 AM (7 years ago)
- Location:
- palm/trunk/SOURCE
- Files:
-
- 15 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/chemistry_model_mod.f90
r3004 r3014 27 27 ! ----------------- 28 28 ! $Id$ 29 ! Bugfix: nzb_do and nzt_do were not used for 3d data output 30 ! 31 ! 3004 2018-04-27 12:33:25Z Giersch 29 32 ! Comment concerning averaged data output added 30 33 ! … … 1152 1155 1153 1156 1154 SUBROUTINE chem_data_output_3d( av, variable, found, local_pf, fill_value )1157 SUBROUTINE chem_data_output_3d( av, variable, found, local_pf, fill_value, nzb_do, nzt_do ) 1155 1158 1156 1159 … … 1163 1166 1164 1167 CHARACTER (LEN=*) :: variable !< 1168 1169 INTEGER(iwp) :: av !< 1170 INTEGER(iwp) :: nzb_do !< lower limit of the data output (usually 0) 1171 INTEGER(iwp) :: nzt_do !< vertical upper limit of the data output (usually nz_do3d) 1172 1165 1173 LOGICAL :: found !< 1166 INTEGER(iwp) :: av !<1167 1174 1168 1175 REAL(wp) :: fill_value !< 1169 REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb :nzt+1) :: local_pf1176 REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) :: local_pf 1170 1177 1171 1178 … … 1189 1196 DO i = nxl, nxr 1190 1197 DO j = nys, nyn 1191 DO k = nzb , nzt+11198 DO k = nzb_do, nzt_do 1192 1199 local_pf(i,j,k) = MERGE( & 1193 1200 chem_species(lsp)%conc(k,j,i), & … … 1201 1208 DO i = nxl, nxr 1202 1209 DO j = nys, nyn 1203 DO k = nzb , nzt+11210 DO k = nzb_do, nzt_do 1204 1211 local_pf(i,j,k) = MERGE( & 1205 1212 chem_species(lsp)%conc_av(k,j,i),& -
palm/trunk/SOURCE/data_output_2d.f90
r3004 r3014 25 25 ! ----------------- 26 26 ! $Id$ 27 ! Added nzb_do and nzt_do for some modules for 2d output 28 ! 29 ! 3004 2018-04-27 12:33:25Z Giersch 27 30 ! precipitation_rate removed, case prr*_xy removed, to_be_resorted have to point 28 31 ! to ql_vp_av and not to ql_vp, allocation checks implemented (averaged data … … 1395 1398 IF ( .NOT. found .AND. radiation ) THEN 1396 1399 CALL radiation_data_output_2d( av, do2d(av,if), found, grid,& 1397 mode, local_pf, two_d ) 1400 mode, local_pf, two_d, & 1401 nzb_do, nzt_do ) 1398 1402 ENDIF 1399 1403 -
palm/trunk/SOURCE/data_output_3d.f90
r3004 r3014 25 25 ! ----------------- 26 26 ! $Id$ 27 ! Added nzb_do and nzt_do for some modules for 3d output 28 ! 29 ! 3004 2018-04-27 12:33:25Z Giersch 27 30 ! Allocation checks implemented (averaged data will be assigned to fill values 28 31 ! if no allocation happened so far) … … 779 782 780 783 IF ( .NOT. found ) THEN 781 CALL tcm_data_output_3d( av, do3d(av,if), found, local_pf ) 784 CALL tcm_data_output_3d( av, do3d(av,if), found, local_pf, & 785 nzb_do, nzt_do ) 782 786 resorted = .TRUE. 783 787 ENDIF … … 787 791 IF ( .NOT. found .AND. radiation ) THEN 788 792 CALL radiation_data_output_3d( av, do3d(av,if), found, & 789 local_pf )793 local_pf, nzb_do, nzt_do ) 790 794 resorted = .TRUE. 791 795 ENDIF … … 803 807 IF ( .NOT. found .AND. air_chemistry ) THEN 804 808 CALL chem_data_output_3d( av, do3d(av,if), found, & 805 local_pf, fill_value )809 local_pf, fill_value, nzb_do, nzt_do ) 806 810 resorted = .TRUE. 807 811 ENDIF … … 811 815 IF ( .NOT. found .AND. plant_canopy ) THEN 812 816 CALL pcm_data_output_3d( av, do3d(av,if), found, local_pf, & 813 fill_value )817 fill_value, nzb_do, nzt_do ) 814 818 resorted = .TRUE. 815 819 ENDIF -
palm/trunk/SOURCE/gust_mod.f90
r3004 r3014 25 25 ! ----------------- 26 26 ! $Id$ 27 ! Bugfix: domain bounds of local_pf corrected 28 ! 29 ! 27 30 ! Interfaces concerning data output updated 28 31 ! … … 408 411 REAL(wp) :: fill_value = -999.0_wp !< value for the _FillValue attribute 409 412 410 REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb :nzt+1) :: local_pf !<413 REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) :: local_pf !< 411 414 412 415 -
palm/trunk/SOURCE/init_3d_model.f90
r3011 r3014 25 25 ! ----------------- 26 26 ! $Id$ 27 ! Bugfix: initialization of ts_value missing 28 ! 29 ! 3011 2018-05-07 14:38:42Z schwenkel 27 30 ! removed redundant if statement 28 31 ! … … 1127 1130 1128 1131 ! 1132 !-- Initialize time series 1133 ts_value = 0.0_wp 1134 1135 ! 1129 1136 !-- Initialize local summation arrays for routine flow_statistics. 1130 1137 !-- This is necessary because they may not yet have been initialized when they -
palm/trunk/SOURCE/land_surface_model_mod.f90
r3004 r3014 25 25 ! ----------------- 26 26 ! $Id$ 27 ! Bugfix: set some initial values 28 ! Bugfix: domain bounds of local_pf corrected 29 ! 30 ! 3004 2018-04-27 12:33:25Z Giersch 27 31 ! Further allocation checks implemented (averaged data will be assigned to fill 28 32 ! values if no allocation happened so far) … … 4639 4643 surf_lsm_h%pavement_surface = .FALSE. 4640 4644 surf_lsm_h%vegetation_surface = .FALSE. 4645 4646 ! 4647 !-- Set default values 4648 surf_lsm_h%r_canopy_min = 0.0_wp 4649 4641 4650 ! 4642 4651 !-- Vertical surfaces … … 4671 4680 surf_lsm_v(l)%vegetation_surface = .FALSE. 4672 4681 4682 4683 ! 4684 !-- Set default values 4685 surf_lsm_v(l)%r_canopy_min = 0.0_wp 4686 4673 4687 ENDDO 4674 4688 … … 5632 5646 REAL(wp) :: fill_value = -999.0_wp !< value for the _FillValue attribute 5633 5647 5634 REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb :nzt+1) :: local_pf !<5648 REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) :: local_pf !< 5635 5649 5636 5650 -
palm/trunk/SOURCE/modules.f90
r3004 r3014 25 25 ! ----------------- 26 26 ! $Id$ 27 ! Added default values of u_max, v_max, and w_max to avoid floating invalid 28 ! during spinup 29 ! 30 ! 3004 2018-04-27 12:33:25Z Giersch 27 31 ! precipitation_rate removed 28 32 ! … … 2043 2047 !< (after each timestep) 2044 2048 2045 REAL(wp) :: u_max !< maximum of absolute u-veloctiy in entire domain2046 REAL(wp) :: v_max !< maximum of absolute v-veloctiy in entire domain2047 REAL(wp) :: w_max !< maximum of absolute w-veloctiy in entire domain2049 REAL(wp) :: u_max = 0.0_wp !< maximum of absolute u-veloctiy in entire domain 2050 REAL(wp) :: v_max = 0.0_wp !< maximum of absolute v-veloctiy in entire domain 2051 REAL(wp) :: w_max = 0.0_wp !< maximum of absolute w-veloctiy in entire domain 2048 2052 2049 2053 REAL(wp), DIMENSION(2) :: z_i !< inversion height -
palm/trunk/SOURCE/plant_canopy_model_mod.f90
r2977 r3014 25 25 ! ----------------- 26 26 ! $Id$ 27 ! Bugfix: nzb_do and nzt_do were not used for 3d data output 28 ! Added pc_transpiration_rate 29 ! 30 ! 2977 2018-04-17 10:27:57Z kanani 27 31 ! Implement changes from branch radiation (r2948-2971) with minor modifications, 28 32 ! plus some formatting. … … 230 234 REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: lad_s !< lad on scalar-grid 231 235 REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: pc_heating_rate !< plant canopy heating rate 236 REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: pc_transpiration_rate !< plant canopy transpiration rate 232 237 233 238 SAVE … … 243 248 ! 244 249 !-- Public variables and constants 245 PUBLIC pc_heating_rate, canopy_mode, cthf, dt_plant_canopy, lad, lad_s, &250 PUBLIC pc_heating_rate, pc_transpiration_rate, canopy_mode, cthf, dt_plant_canopy, lad, lad_s, & 246 251 pch_index 247 252 … … 315 320 unit = 'K s-1' 316 321 322 CASE ( 'pcm_transpirationrate' ) 323 unit = 'kg kg-1 s-1' 324 317 325 CASE ( 'pcm_lad' ) 318 326 unit = 'm2 m-3' … … 404 412 !> Subroutine defining 3D output variables 405 413 !------------------------------------------------------------------------------! 406 SUBROUTINE pcm_data_output_3d( av, variable, found, local_pf, fill_value ) 407 408 USE control_parameters, & 409 ONLY : nz_do3d 410 414 SUBROUTINE pcm_data_output_3d( av, variable, found, local_pf, fill_value, & 415 nzb_do, nzt_do ) 416 411 417 USE indices 412 418 … … 423 429 INTEGER(iwp) :: k !< 424 430 INTEGER(iwp) :: k_topo !< topography top index 431 INTEGER(iwp) :: nzb_do !< lower limit of the data output (usually 0) 432 INTEGER(iwp) :: nzt_do !< vertical upper limit of the data output (usually nz_do3d) 425 433 426 434 LOGICAL :: found !< 427 435 428 436 REAL(wp) :: fill_value 429 REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb :nz_do3d) :: local_pf !<437 REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) :: local_pf !< 430 438 431 439 … … 449 457 ENDDO 450 458 ENDIF 451 459 460 CASE ( 'pcm_transpirationrate' ) 461 IF ( av == 0 ) THEN 462 DO i = nxl, nxr 463 DO j = nys, nyn 464 IF ( pch_index_ji(j,i) /= 0 ) THEN 465 k_topo = get_topography_top_index_ji( j, i, 's' ) 466 DO k = k_topo, k_topo + pch_index_ji(j,i) 467 local_pf(i,j,k) = pc_transpiration_rate(k-k_topo,j,i) 468 ENDDO 469 ENDIF 470 ENDDO 471 ENDDO 472 ENDIF 452 473 453 474 CASE ( 'pcm_lad' ) … … 497 518 SELECT CASE ( TRIM( var ) ) 498 519 499 CASE ( 'pcm_heatrate', 'pcm_lad' 520 CASE ( 'pcm_heatrate', 'pcm_lad', 'pcm_transpirationrate') 500 521 grid_x = 'x' 501 522 grid_y = 'y' … … 873 894 874 895 ALLOCATE( cum_lai_hf(nzb:nzt+1,nysg:nyng,nxlg:nxrg), & 875 pc_heating_rate(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ) 896 pc_heating_rate(nzb:nzt+1,nysg:nyng,nxlg:nxrg), & 897 pc_transpiration_rate(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ) 876 898 ! 877 899 !-- Piecewise calculation of the cumulative leaf area index by vertical … … 1397 1419 1398 1420 kk = k - k_wall !- lad arrays are defined flat 1399 tend(k,j,i) = tend(k,j,i) - & 1400 lsec * & 1401 lad_s(kk,j,i) * & 1421 pc_transpiration_rate(kk,j,i) = - lsec & 1422 * lad_s(kk,j,i) * & 1402 1423 SQRT( ( 0.5_wp * ( u(k,j,i) + & 1403 1424 u(k,j,i+1) ) & … … 1411 1432 ) * & 1412 1433 ( q(k,j,i) - lsc ) 1434 1435 tend(k,j,i) = tend(k,j,i) + pc_transpiration_rate(kk,j,i) 1413 1436 ENDDO 1414 1437 ENDDO … … 1728 1751 1729 1752 DO k = k_wall + 1, k_wall + pch_index_ji(j,i) 1730 1731 kk = k - k_wall 1732 tend(k,j,i) = tend(k,j,i) - & 1733 lsec * & 1734 lad_s(kk,j,i) * & 1753 kk = k - k_wall !- lad arrays are defined flat 1754 1755 pc_transpiration_rate(kk,j,i) = - lsec & 1756 * lad_s(kk,j,i) * & 1735 1757 SQRT( ( 0.5_wp * ( u(k,j,i) + & 1736 1758 u(k,j,i+1) ) & … … 1744 1766 ) * & 1745 1767 ( q(k,j,i) - lsc ) 1768 1769 tend(k,j,i) = tend(k,j,i) + pc_transpiration_rate(kk,j,i) 1770 1746 1771 ENDDO 1747 1772 -
palm/trunk/SOURCE/prognostic_equations.f90
r2815 r3014 25 25 ! ----------------- 26 26 ! $Id$ 27 ! Fixed a bug in the IF condition to call pcm_tendency in case of 28 ! potential temperature 29 ! 30 ! 2815 2018-02-19 11:29:57Z kanani 27 31 ! Rename chem_tendency to chem_prognostic_equations, 28 32 ! implement vector version for air chemistry … … 298 302 timestep_scheme, tsc, use_subsidence_tendencies, & 299 303 use_upstream_for_tke, wind_turbine, ws_scheme_mom, & 300 ws_scheme_sca 304 ws_scheme_sca, urban_surface, land_surface 301 305 302 306 USE cpulog, & … … 759 763 ! 760 764 !-- Consideration of heat sources within the plant canopy 761 IF ( plant_canopy .AND. cthf /= 0.0_wp ) THEN 765 IF ( plant_canopy .AND. & 766 (cthf /= 0.0_wp .OR. urban_surface .OR. land_surface) ) THEN 762 767 CALL pcm_tendency( i, j, 4 ) 763 768 ENDIF … … 1325 1330 1326 1331 1327 1328 1329 1332 CALL cpu_log( log_point(32), 'all progn.equations', 'stop' ) 1330 1333 … … 1671 1674 ! 1672 1675 !-- Consideration of heat sources within the plant canopy 1673 IF ( plant_canopy .AND. ( cthf /= 0.0_wp ) ) THEN 1676 IF ( plant_canopy .AND. & 1677 (cthf /= 0.0_wp .OR. urban_surface .OR. land_surface) ) THEN 1674 1678 CALL pcm_tendency( 4 ) 1675 1679 ENDIF … … 1718 1722 ENDDO 1719 1723 ENDDO 1720 1721 1724 ! 1722 1725 !-- Calculate tendencies for the next Runge-Kutta step -
palm/trunk/SOURCE/radiation_model_mod.f90
r3004 r3014 28 28 ! ----------------- 29 29 ! $Id$ 30 ! Introduced plant canopy height similar to urban canopy height to limit 31 ! the memory requirement to allocate lad. 32 ! Deactivated automatic setting of minimum raytracing distance. 33 ! 34 ! 3004 2018-04-27 12:33:25Z Giersch 30 35 ! Further allocation checks implemented (averaged data will be assigned to fill 31 36 ! values if no allocation happened so far) … … 329 334 330 335 USE cloud_parameters, & 331 ONLY: cp, l_d_cp, r_d, rho_l336 ONLY: cp, l_d_cp, l_v, r_d, rho_l 332 337 333 338 USE constants, & … … 372 377 373 378 USE plant_canopy_model_mod, & 374 ONLY: pc_heating_rate, lad_s379 ONLY: lad_s, pc_heating_rate, pc_transpiration_rate 375 380 376 381 USE pegrid … … 646 651 !-- Parameters of urban and land surface models 647 652 INTEGER(iwp) :: nzu !< number of layers of urban surface (will be calculated) 653 INTEGER(iwp) :: nzp !< number of layers of plant canopy (will be calculated) 648 654 INTEGER(iwp) :: nzub,nzut !< bottom and top layer of urban surface (will be calculated) 655 INTEGER(iwp) :: nzpt !< top layer of plant canopy (will be calculated) 649 656 !-- parameters of urban and land surface models 650 657 INTEGER(iwp), PARAMETER :: nzut_free = 3 !< number of free layers above top of of topography … … 4324 4331 REAL(wp), DIMENSION(3) :: sunorig_grid !< grid squashed solar direction unit vector (zyx) 4325 4332 REAL(wp), DIMENSION(0:nsurf_type) :: costheta !< direct irradiance factor of solar angle 4326 REAL(wp), DIMENSION(nzub:nzut) :: pchf_prep !< precalculated factor for canopy temp tendency 4333 REAL(wp), DIMENSION(nzub:nzut) :: pchf_prep !< precalculated factor for canopy temperature tendency 4334 REAL(wp), DIMENSION(nzub:nzut) :: pctf_prep !< precalculated factor for canopy transpiration tendency 4327 4335 REAL(wp), PARAMETER :: alpha = 0._wp !< grid rotation (TODO: add to namelist or remove) 4328 4336 REAL(wp) :: pc_box_area, pc_abs_frac, pc_abs_eff … … 4345 4353 REAL(wp) :: area_surf !< total area of surfaces in all processor 4346 4354 4355 4356 4347 4357 #if ! defined( __nopointer ) 4348 4358 IF ( plant_canopy ) THEN 4349 4359 pchf_prep(:) = r_d * (hyp(nzub:nzut) / 100000.0_wp)**0.286_wp & 4350 4360 / (cp * hyp(nzub:nzut) * dx*dy*dz) !< equals to 1 / (rho * c_p * Vbox * T) 4361 pctf_prep(:) = r_d * (hyp(nzub:nzut) / 100000.0_wp)**0.286_wp & 4362 / (l_v * hyp(nzub:nzut) * dx*dy*dz) 4351 4363 ENDIF 4352 4364 #endif … … 4619 4631 !-- push heat flux absorbed by plant canopy to respective 3D arrays 4620 4632 IF ( npcbl > 0 ) THEN 4621 pc_heating_rate(:,:,:) = 0._wp 4633 pc_heating_rate(:,:,:) = 0.0_wp 4634 pc_transpiration_rate(:,:,:) = 0.0_wp 4622 4635 DO ipcgb = 1, npcbl 4623 4636 … … 4630 4643 pc_heating_rate(kk, j, i) = (pcbinsw(ipcgb) + pcbinlw(ipcgb)) & 4631 4644 * pchf_prep(k) * pt(k, j, i) !-- = dT/dt 4645 4646 ! pc_transpiration_rate(kk,j,i) = 0.75_wp* (pcbinsw(ipcgb) + pcbinlw(ipcgb)) & 4647 ! * pctf_prep(k) * pt(k, j, i) !-- = dq/dt 4648 4632 4649 ENDDO 4633 4650 ENDIF … … 4995 5012 INTEGER(iwp) :: k_topo !< vertical index indicating topography top for given (j,i) 4996 5013 INTEGER(iwp) :: k_topo2 !< vertical index indicating topography top for given (j,i) 4997 INTEGER(iwp) :: nz ubl, nzutl, isurf, ipcgb5014 INTEGER(iwp) :: nzptl, nzubl, nzutl, isurf, ipcgb 4998 5015 INTEGER(iwp) :: procid 4999 5016 REAL(wp) :: mrl … … 5040 5057 5041 5058 nzutl = MAX( nzutl, MAXVAL( pct ) ) 5059 nzptl = MAXVAL( pct ) 5042 5060 !-- code of plant canopy model uses parameter pch_index 5043 5061 !-- we need to setup it here to right value … … 5058 5076 CALL MPI_AllReduce(nzubl, nzub, 1, MPI_INTEGER, MPI_MIN, comm2d, ierr ) 5059 5077 CALL MPI_AllReduce(nzutl, nzut, 1, MPI_INTEGER, MPI_MAX, comm2d, ierr ) 5078 CALL MPI_AllReduce(nzptl, nzpt, 1, MPI_INTEGER, MPI_MAX, comm2d, ierr ) 5060 5079 #else 5061 5080 nzub = nzubl 5062 5081 nzut = nzutl 5082 nzpt = nzptl 5063 5083 #endif 5064 5084 ! 5065 !-- global number of urban layers5085 !-- global number of urban and plant layers 5066 5086 nzu = nzut - nzub + 1 5087 nzp = nzpt - nzub + 1 5067 5088 ! 5068 5089 !-- check max_raytracing_dist relative to urban surface layer height 5069 mrl = 2.0_wp * nzu * dz5070 IF ( max_raytracing_dist <= mrl ) THEN5071 IF ( max_raytracing_dist /= -999.0_wp ) THEN5072 ! -- max_raytracing_dist too low5073 WRITE(message_string, '(a,f6.1)') 'Max_raytracing_dist too low, ' &5074 // 'override to value ', mrl5075 CALL message('radiation_interaction_init', 'PA0521', 0, 0, -1, 6, 0)5076 ENDIF5077 max_raytracing_dist = mrl5078 ENDIF5090 ! mrl = 2.0_wp * nzu * dz 5091 ! IF ( max_raytracing_dist <= mrl ) THEN 5092 ! IF ( max_raytracing_dist /= -999.0_wp ) THEN 5093 ! !-- max_raytracing_dist too low 5094 ! WRITE(message_string, '(a,f6.1)') 'Max_raytracing_dist too low, ' & 5095 ! // 'override to value ', mrl 5096 ! CALL message('radiation_interaction_init', 'PA0521', 0, 0, -1, 6, 0) 5097 ! ENDIF 5098 ! max_raytracing_dist = mrl 5099 ! ENDIF 5079 5100 ! 5080 5101 !-- allocate urban surfaces grid … … 5103 5124 IF ( npcbl > 0 ) THEN 5104 5125 ALLOCATE( pcbl(iz:ix, 1:npcbl) ) 5105 ALLOCATE( gridpcbl(nzub:nz ut,nys:nyn,nxl:nxr) )5126 ALLOCATE( gridpcbl(nzub:nzpt,nys:nyn,nxl:nxr) ) 5106 5127 pcbl = -1 5107 5128 gridpcbl(:,:,:) = 0 … … 5388 5409 IF ( plant_canopy ) THEN 5389 5410 ALLOCATE( plantt(0:(nx+1)*(ny+1)-1) ) 5390 maxboxesg = nx + ny + nz u+ 15411 maxboxesg = nx + ny + nzp + 1 5391 5412 max_track_len = nx + ny + 1 5392 5413 !-- temporary arrays storing values for csf calculation during raytracing … … 5416 5437 !-- optimization of memory should be done 5417 5438 !-- Argument X of function STORAGE_SIZE(X) needs arbitrary REAL(wp) value, set to 1.0_wp for now 5418 size_lad_rma = STORAGE_SIZE(1.0_wp)/8*nnx*nny*nz u5439 size_lad_rma = STORAGE_SIZE(1.0_wp)/8*nnx*nny*nzp 5419 5440 CALL MPI_Win_allocate(size_lad_rma, STORAGE_SIZE(1.0_wp)/8, minfo, comm2d, & 5420 5441 lad_s_rma_p, win_lad, ierr) 5421 CALL c_f_pointer(lad_s_rma_p, lad_s_rma, (/ nz u, nny, nnx /))5442 CALL c_f_pointer(lad_s_rma_p, lad_s_rma, (/ nzp, nny, nnx /)) 5422 5443 sub_lad(nzub:, nys:, nxl:) => lad_s_rma(:,:,:) 5423 5444 ELSE 5424 ALLOCATE(sub_lad(nzub:nz ut, nys:nyn, nxl:nxr))5445 ALLOCATE(sub_lad(nzub:nzpt, nys:nyn, nxl:nxr)) 5425 5446 ENDIF 5426 5447 #else 5427 5448 plantt = RESHAPE( pct(nys:nyn,nxl:nxr), (/(nx+1)*(ny+1)/) ) 5428 ALLOCATE(sub_lad(nzub:nz ut, nys:nyn, nxl:nxr))5449 ALLOCATE(sub_lad(nzub:nzpt, nys:nyn, nxl:nxr)) 5429 5450 #endif 5430 5451 plantt_max = MAXVAL(plantt) … … 5437 5458 k = get_topography_top_index_ji( j, i, 's' ) 5438 5459 5439 sub_lad(k:nz ut, j, i) = lad_s(0:nzut-k, j, i)5460 sub_lad(k:nzpt, j, i) = lad_s(0:nzpt-k, j, i) 5440 5461 ENDDO 5441 5462 ENDDO … … 5446 5467 CALL MPI_Win_lock_all(0, win_lad, ierr) 5447 5468 ELSE 5448 ALLOCATE( sub_lad_g(0:(nx+1)*(ny+1)*nz u-1) )5449 CALL MPI_AllGather( sub_lad, nnx*nny*nz u, MPI_REAL, &5450 sub_lad_g, nnx*nny*nz u, MPI_REAL, comm2d, ierr )5469 ALLOCATE( sub_lad_g(0:(nx+1)*(ny+1)*nzp-1) ) 5470 CALL MPI_AllGather( sub_lad, nnx*nny*nzp, MPI_REAL, & 5471 sub_lad_g, nnx*nny*nzp, MPI_REAL, comm2d, ierr ) 5451 5472 ENDIF 5452 5473 #endif … … 6142 6163 #if defined( __parallel ) 6143 6164 lad_ip(ncsb) = ip 6144 lad_disp(ncsb) = (box(3)-px*nnx)*(nny*nz u) + (box(2)-py*nny)*nzu+ box(1)-nzub6165 lad_disp(ncsb) = (box(3)-px*nnx)*(nny*nzp) + (box(2)-py*nny)*nzp + box(1)-nzub 6145 6166 #endif 6146 6167 ENDIF … … 6185 6206 lad_s_target = lad_s_ray(i) 6186 6207 ELSE 6187 lad_s_target = sub_lad_g(lad_ip(i)*nnx*nny*nz u+ lad_disp(i))6208 lad_s_target = sub_lad_g(lad_ip(i)*nnx*nny*nzp + lad_disp(i)) 6188 6209 ENDIF 6189 6210 #else … … 6387 6408 ig = ip*nnx*nny + (rt2_track(2,i)-px*nnx)*nny + rt2_track(1,i)-py*nny 6388 6409 IF ( plantt(ig) <= nzterr(ig) ) CYCLE 6389 wdisp = (rt2_track(2,i)-px*nnx)*(nny*nz u) + (rt2_track(1,i)-py*nny)*nzu+ nzterr(ig)+1-nzub6410 wdisp = (rt2_track(2,i)-px*nnx)*(nny*nzp) + (rt2_track(1,i)-py*nny)*nzp + nzterr(ig)+1-nzub 6390 6411 wcount = plantt(ig)-nzterr(ig) 6391 6412 ! TODO send request ASAP - even during raytracing … … 6411 6432 py = rt2_track(1,i)/nny 6412 6433 ip = px*pdims(2)+py 6413 ig = ip*nnx*nny*nz u + (rt2_track(2,i)-px*nnx)*(nny*nzu) + (rt2_track(1,i)-py*nny)*nzu6434 ig = ip*nnx*nny*nzp + (rt2_track(2,i)-px*nnx)*(nny*nzp) + (rt2_track(1,i)-py*nny)*nzp 6414 6435 rt2_track_lad(nzub:plantt_max, i) = sub_lad_g(ig:ig+nly-1) 6415 6436 ENDDO … … 6429 6450 !--Assert that we have space allocated for CSFs 6430 6451 !-- 6431 maxboxes = (ntrack + MAX(origin(1) - nzub, nz ut - origin(1))) * SIZE(zdirs, 1)6452 maxboxes = (ntrack + MAX(origin(1) - nzub, nzpt - origin(1))) * SIZE(zdirs, 1) 6432 6453 IF ( ncsfl + maxboxes > ncsfla ) THEN 6433 6454 !-- use this code for growing by fixed exponential increments (equivalent to case where ncsfl always increases by 1) … … 6814 6835 ENDIF 6815 6836 ! 6816 !-- Close binary file 6837 !-- Close binary file 6817 6838 CALL close_file( fsvf ) 6818 6839 … … 7617 7638 !------------------------------------------------------------------------------! 7618 7639 SUBROUTINE radiation_data_output_2d( av, variable, found, grid, mode, & 7619 local_pf, two_d )7640 local_pf, two_d, nzb_do, nzt_do ) 7620 7641 7621 7642 USE indices … … 7635 7656 INTEGER(iwp) :: k !< 7636 7657 INTEGER(iwp) :: m !< index of surface element at grid point (j,i) 7658 INTEGER(iwp) :: nzb_do !< 7659 INTEGER(iwp) :: nzt_do !< 7637 7660 7638 7661 LOGICAL :: found !< … … 7641 7664 REAL(wp) :: fill_value = -999.0_wp !< value for the _FillValue attribute 7642 7665 7643 REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb :nzt+1) :: local_pf !<7666 REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) :: local_pf !< 7644 7667 7645 7668 found = .TRUE. … … 7685 7708 DO i = nxl, nxr 7686 7709 DO j = nys, nyn 7687 DO k = nzb , nzt+17710 DO k = nzb_do, nzt_do 7688 7711 local_pf(i,j,k) = rad_lw_in(k,j,i) 7689 7712 ENDDO … … 7697 7720 DO i = nxl, nxr 7698 7721 DO j = nys, nyn 7699 DO k = nzb , nzt+17722 DO k = nzb_do, nzt_do 7700 7723 local_pf(i,j,k) = rad_lw_in_av(k,j,i) 7701 7724 ENDDO … … 7709 7732 DO i = nxl, nxr 7710 7733 DO j = nys, nyn 7711 DO k = nzb , nzt+17734 DO k = nzb_do, nzt_do 7712 7735 local_pf(i,j,k) = rad_lw_out(k,j,i) 7713 7736 ENDDO … … 7721 7744 DO i = nxl, nxr 7722 7745 DO j = nys, nyn 7723 DO k = nzb , nzt+17746 DO k = nzb_do, nzt_do 7724 7747 local_pf(i,j,k) = rad_lw_out_av(k,j,i) 7725 7748 ENDDO … … 7733 7756 DO i = nxl, nxr 7734 7757 DO j = nys, nyn 7735 DO k = nzb , nzt+17758 DO k = nzb_do, nzt_do 7736 7759 local_pf(i,j,k) = rad_lw_cs_hr(k,j,i) 7737 7760 ENDDO … … 7745 7768 DO i = nxl, nxr 7746 7769 DO j = nys, nyn 7747 DO k = nzb , nzt+17770 DO k = nzb_do, nzt_do 7748 7771 local_pf(i,j,k) = rad_lw_cs_hr_av(k,j,i) 7749 7772 ENDDO … … 7757 7780 DO i = nxl, nxr 7758 7781 DO j = nys, nyn 7759 DO k = nzb , nzt+17782 DO k = nzb_do, nzt_do 7760 7783 local_pf(i,j,k) = rad_lw_hr(k,j,i) 7761 7784 ENDDO … … 7769 7792 DO i = nxl, nxr 7770 7793 DO j = nys, nyn 7771 DO k = nzb , nzt+17794 DO k = nzb_do, nzt_do 7772 7795 local_pf(i,j,k) = rad_lw_hr_av(k,j,i) 7773 7796 ENDDO … … 7781 7804 DO i = nxl, nxr 7782 7805 DO j = nys, nyn 7783 DO k = nzb , nzt+17806 DO k = nzb_do, nzt_do 7784 7807 local_pf(i,j,k) = rad_sw_in(k,j,i) 7785 7808 ENDDO … … 7793 7816 DO i = nxl, nxr 7794 7817 DO j = nys, nyn 7795 DO k = nzb , nzt+17818 DO k = nzb_do, nzt_do 7796 7819 local_pf(i,j,k) = rad_sw_in_av(k,j,i) 7797 7820 ENDDO … … 7805 7828 DO i = nxl, nxr 7806 7829 DO j = nys, nyn 7807 DO k = nzb , nzt+17830 DO k = nzb_do, nzt_do 7808 7831 local_pf(i,j,k) = rad_sw_out(k,j,i) 7809 7832 ENDDO … … 7829 7852 DO i = nxl, nxr 7830 7853 DO j = nys, nyn 7831 DO k = nzb , nzt+17854 DO k = nzb_do, nzt_do 7832 7855 local_pf(i,j,k) = rad_sw_cs_hr(k,j,i) 7833 7856 ENDDO … … 7841 7864 DO i = nxl, nxr 7842 7865 DO j = nys, nyn 7843 DO k = nzb , nzt+17866 DO k = nzb_do, nzt_do 7844 7867 local_pf(i,j,k) = rad_sw_cs_hr_av(k,j,i) 7845 7868 ENDDO … … 7853 7876 DO i = nxl, nxr 7854 7877 DO j = nys, nyn 7855 DO k = nzb , nzt+17878 DO k = nzb_do, nzt_do 7856 7879 local_pf(i,j,k) = rad_sw_hr(k,j,i) 7857 7880 ENDDO … … 7865 7888 DO i = nxl, nxr 7866 7889 DO j = nys, nyn 7867 DO k = nzb , nzt+17890 DO k = nzb_do, nzt_do 7868 7891 local_pf(i,j,k) = rad_sw_hr_av(k,j,i) 7869 7892 ENDDO … … 7888 7911 !> Subroutine defining 3D output variables 7889 7912 !------------------------------------------------------------------------------! 7890 SUBROUTINE radiation_data_output_3d( av, variable, found, local_pf )7913 SUBROUTINE radiation_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do ) 7891 7914 7892 7915 … … 7904 7927 INTEGER(iwp) :: j !< 7905 7928 INTEGER(iwp) :: k !< 7929 INTEGER(iwp) :: nzb_do !< 7930 INTEGER(iwp) :: nzt_do !< 7906 7931 7907 7932 LOGICAL :: found !< … … 7909 7934 REAL(wp) :: fill_value = -999.0_wp !< value for the _FillValue attribute 7910 7935 7911 REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb :nzt+1) :: local_pf !<7936 REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) :: local_pf !< 7912 7937 7913 7938 … … 7921 7946 DO i = nxl, nxr 7922 7947 DO j = nys, nyn 7923 DO k = nzb , nzt+17948 DO k = nzb_do, nzt_do 7924 7949 local_pf(i,j,k) = rad_sw_in(k,j,i) 7925 7950 ENDDO … … 7933 7958 DO i = nxl, nxr 7934 7959 DO j = nys, nyn 7935 DO k = nzb , nzt+17960 DO k = nzb_do, nzt_do 7936 7961 local_pf(i,j,k) = rad_sw_in_av(k,j,i) 7937 7962 ENDDO … … 7944 7969 DO i = nxl, nxr 7945 7970 DO j = nys, nyn 7946 DO k = nzb , nzt+17971 DO k = nzb_do, nzt_do 7947 7972 local_pf(i,j,k) = rad_sw_out(k,j,i) 7948 7973 ENDDO … … 7956 7981 DO i = nxl, nxr 7957 7982 DO j = nys, nyn 7958 DO k = nzb , nzt+17983 DO k = nzb_do, nzt_do 7959 7984 local_pf(i,j,k) = rad_sw_out_av(k,j,i) 7960 7985 ENDDO … … 7967 7992 DO i = nxl, nxr 7968 7993 DO j = nys, nyn 7969 DO k = nzb , nzt+17994 DO k = nzb_do, nzt_do 7970 7995 local_pf(i,j,k) = rad_sw_cs_hr(k,j,i) 7971 7996 ENDDO … … 7979 8004 DO i = nxl, nxr 7980 8005 DO j = nys, nyn 7981 DO k = nzb , nzt+18006 DO k = nzb_do, nzt_do 7982 8007 local_pf(i,j,k) = rad_sw_cs_hr_av(k,j,i) 7983 8008 ENDDO … … 7990 8015 DO i = nxl, nxr 7991 8016 DO j = nys, nyn 7992 DO k = nzb , nzt+18017 DO k = nzb_do, nzt_do 7993 8018 local_pf(i,j,k) = rad_sw_hr(k,j,i) 7994 8019 ENDDO … … 8002 8027 DO i = nxl, nxr 8003 8028 DO j = nys, nyn 8004 DO k = nzb , nzt+18029 DO k = nzb_do, nzt_do 8005 8030 local_pf(i,j,k) = rad_sw_hr_av(k,j,i) 8006 8031 ENDDO … … 8013 8038 DO i = nxl, nxr 8014 8039 DO j = nys, nyn 8015 DO k = nzb , nzt+18040 DO k = nzb_do, nzt_do 8016 8041 local_pf(i,j,k) = rad_lw_in(k,j,i) 8017 8042 ENDDO … … 8025 8050 DO i = nxl, nxr 8026 8051 DO j = nys, nyn 8027 DO k = nzb , nzt+18052 DO k = nzb_do, nzt_do 8028 8053 local_pf(i,j,k) = rad_lw_in_av(k,j,i) 8029 8054 ENDDO … … 8036 8061 DO i = nxl, nxr 8037 8062 DO j = nys, nyn 8038 DO k = nzb , nzt+18063 DO k = nzb_do, nzt_do 8039 8064 local_pf(i,j,k) = rad_lw_out(k,j,i) 8040 8065 ENDDO … … 8048 8073 DO i = nxl, nxr 8049 8074 DO j = nys, nyn 8050 DO k = nzb , nzt+18075 DO k = nzb_do, nzt_do 8051 8076 local_pf(i,j,k) = rad_lw_out_av(k,j,i) 8052 8077 ENDDO … … 8059 8084 DO i = nxl, nxr 8060 8085 DO j = nys, nyn 8061 DO k = nzb , nzt+18086 DO k = nzb_do, nzt_do 8062 8087 local_pf(i,j,k) = rad_lw_cs_hr(k,j,i) 8063 8088 ENDDO … … 8071 8096 DO i = nxl, nxr 8072 8097 DO j = nys, nyn 8073 DO k = nzb , nzt+18098 DO k = nzb_do, nzt_do 8074 8099 local_pf(i,j,k) = rad_lw_cs_hr_av(k,j,i) 8075 8100 ENDDO … … 8082 8107 DO i = nxl, nxr 8083 8108 DO j = nys, nyn 8084 DO k = nzb , nzt+18109 DO k = nzb_do, nzt_do 8085 8110 local_pf(i,j,k) = rad_lw_hr(k,j,i) 8086 8111 ENDDO … … 8094 8119 DO i = nxl, nxr 8095 8120 DO j = nys, nyn 8096 DO k = nzb , nzt+18121 DO k = nzb_do, nzt_do 8097 8122 local_pf(i,j,k) = rad_lw_hr_av(k,j,i) 8098 8123 ENDDO -
palm/trunk/SOURCE/time_integration.f90
r3004 r3014 25 25 ! ----------------- 26 26 ! $Id$ 27 ! Fixed bug in IF statement 28 ! Ensure that the time when calling the radiation to be the time step of the 29 ! pre-calculated time when first calculate the positions of the sun 30 ! 31 ! 3004 2018-04-27 12:33:25Z Giersch 27 32 ! First call of flow_statistics has been removed. It is already called in 28 33 ! run_control itself … … 491 496 492 497 CHARACTER (LEN=9) :: time_to_string !< 493 INTEGER :: n 494 INTEGER :: lsp 498 INTEGER(iwp) :: it 499 INTEGER(iwp) :: lsp 500 INTEGER(iwp) :: n 501 495 502 496 503 REAL(wp) :: dt_3d_old !< temporary storage of timestep to be used for 497 504 !< steering of run control output interval 505 REAL(wp) :: tsrp_org !< original value of time_since_reference_point 498 506 ! 499 507 !-- At beginning determine the first time step … … 1040 1048 ENDIF 1041 1049 1050 ! 1051 !-- Adjust the current_ time to the time step of the radiation model. 1052 !-- Needed since radiation is pre-calculated and stored only on apparent 1053 !-- solar positions 1054 it = FLOOR(time_since_reference_point/dt_radiation) 1055 tsrp_org = time_since_reference_point 1056 time_since_reference_point = REAL(it,wp) * dt_radiation 1057 1042 1058 CALL radiation_control 1043 1059 … … 1050 1066 CALL cpu_log( log_point(75), 'radiation_interaction', 'stop' ) 1051 1067 ENDIF 1068 1069 ! 1070 !-- Return the current time to its original value 1071 time_since_reference_point = tsrp_org 1052 1072 1053 1073 ENDIF -
palm/trunk/SOURCE/turbulence_closure_mod.f90
r3004 r3014 25 25 ! ----------------- 26 26 ! $Id$ 27 ! Bugfix: nzb_do and nzt_do were not used for 3d data output 28 ! 29 ! 3004 2018-04-27 12:33:25Z Giersch 27 30 ! Further allocation checks implemented 28 31 ! … … 626 629 REAL(wp) :: fill_value = -999.0_wp !< value for the _FillValue attribute 627 630 628 REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb :nzt+1) :: local_pf !< local631 REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) :: local_pf !< local 629 632 !< array to which output data is resorted to 630 633 … … 723 726 !> Define 3D output variables. 724 727 !------------------------------------------------------------------------------! 725 SUBROUTINE tcm_data_output_3d( av, variable, found, local_pf )728 SUBROUTINE tcm_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do ) 726 729 727 730 … … 733 736 CHARACTER (LEN=*) :: variable !< 734 737 735 INTEGER(iwp) :: av !< 736 INTEGER(iwp) :: i !< 737 INTEGER(iwp) :: j !< 738 INTEGER(iwp) :: k !< 738 INTEGER(iwp) :: av !< 739 INTEGER(iwp) :: i !< 740 INTEGER(iwp) :: j !< 741 INTEGER(iwp) :: k !< 742 INTEGER(iwp) :: nzb_do !< lower limit of the data output (usually 0) 743 INTEGER(iwp) :: nzt_do !< vertical upper limit of the data output (usually nz_do3d) 739 744 740 745 LOGICAL :: found !< … … 742 747 REAL(wp) :: fill_value = -999.0_wp !< value for the _FillValue attribute 743 748 744 REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb :nzt+1) :: local_pf !< local749 REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) :: local_pf !< local 745 750 !< array to which output data is resorted to 746 751 … … 756 761 DO i = nxl, nxr 757 762 DO j = nys, nyn 758 DO k = nzb , nzt+1763 DO k = nzb_do, nzt_do 759 764 local_pf(i,j,k) = diss(k,j,i) 760 765 ENDDO … … 768 773 DO i = nxl, nxr 769 774 DO j = nys, nyn 770 DO k = nzb , nzt+1775 DO k = nzb_do, nzt_do 771 776 local_pf(i,j,k) = diss_av(k,j,i) 772 777 ENDDO … … 779 784 DO i = nxl, nxr 780 785 DO j = nys, nyn 781 DO k = nzb , nzt+1786 DO k = nzb_do, nzt_do 782 787 local_pf(i,j,k) = kh(k,j,i) 783 788 ENDDO … … 791 796 DO i = nxl, nxr 792 797 DO j = nys, nyn 793 DO k = nzb , nzt+1798 DO k = nzb_do, nzt_do 794 799 local_pf(i,j,k) = kh_av(k,j,i) 795 800 ENDDO … … 802 807 DO i = nxl, nxr 803 808 DO j = nys, nyn 804 DO k = nzb , nzt+1809 DO k = nzb_do, nzt_do 805 810 local_pf(i,j,k) = km(k,j,i) 806 811 ENDDO … … 814 819 DO i = nxl, nxr 815 820 DO j = nys, nyn 816 DO k = nzb , nzt+1821 DO k = nzb_do, nzt_do 817 822 local_pf(i,j,k) = km_av(k,j,i) 818 823 ENDDO … … 825 830 DO i = nxl, nxr 826 831 DO j = nys, nyn 827 DO k = nzb , nzt+1832 DO k = nzb_do, nzt_do 828 833 local_pf(i,j,k) = dummy1(k,j,i) 829 834 ENDDO … … 836 841 DO i = nxl, nxr 837 842 DO j = nys, nyn 838 DO k = nzb , nzt+1843 DO k = nzb_do, nzt_do 839 844 local_pf(i,j,k) = dummy2(k,j,i) 840 845 ENDDO … … 847 852 DO i = nxl, nxr 848 853 DO j = nys, nyn 849 DO k = nzb , nzt+1854 DO k = nzb_do, nzt_do 850 855 local_pf(i,j,k) = dummy3(k,j,i) 851 856 ENDDO -
palm/trunk/SOURCE/urban_surface_mod.f90
r2977 r3014 28 28 ! ----------------- 29 29 ! $Id$ 30 ! Added pc_transpiration_rate 31 ! 32 ! 2977 2018-04-17 10:27:57Z kanani 30 33 ! Implement changes from branch radiation (r2948-2971) with minor modifications. 31 34 ! (moh.hefny): … … 264 267 !> by zero, e.g. in case fraq(0,m) + fraq(1,m) = 0?! 265 268 !> @todo Use unit 90 for OPEN/CLOSE of input files (FK) 269 !> @todo Move plant canopy stuff into plant canopy code 266 270 !------------------------------------------------------------------------------! 267 271 MODULE urban_surface_mod … … 309 313 310 314 USE plant_canopy_model_mod, & 311 ONLY: pc_heating_rate 315 ONLY: pc_heating_rate, pc_transpiration_rate 312 316 313 317 USE radiation_model_mod, & … … 2361 2365 INTEGER(iwp) :: ids,idsint,idsidx,isurf,isvf,isurfs,isurflt 2362 2366 INTEGER(iwp) :: is,js,ks,i,j,k,iwl,istat, l, m 2363 INTEGER(iwp) :: 2367 INTEGER(iwp) :: k_topo !< topography top index 2364 2368 2365 2369 dirstart = (/ startland, startwall, startwall, startwall, startwall /) … … 4539 4543 !-- in case of cthf /= 0 => we need to allocate it for our use here 4540 4544 ALLOCATE( pc_heating_rate(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ) 4545 4546 pc_heating_rate = 0.0_wp 4547 4548 ENDIF 4549 4550 IF ( .NOT. ALLOCATED( pc_transpiration_rate) ) THEN 4551 !-- then pc_heating_rate is allocated in init_plant_canopy 4552 !-- in case of cthf /= 0 => we need to allocate it for our use here 4553 ALLOCATE( pc_transpiration_rate(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ) 4554 4555 pc_transpiration_rate = 0.0_wp 4556 4557 4541 4558 ENDIF 4542 4559 ENDIF -
palm/trunk/SOURCE/user_data_output_2d.f90
r3004 r3014 25 25 ! ----------------- 26 26 ! $Id$ 27 ! Bugfix: domain bounds of local_pf corrected 28 ! 29 ! 3004 2018-04-27 12:33:25Z Giersch 27 30 ! Further allocation checks implemented (averaged data will be assigned to fill 28 31 ! values if no allocation happened so far) … … 100 103 REAL(wp) :: fill_value = -999.0_wp !< value for the _FillValue attribute 101 104 102 REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb :nzt+1) :: local_pf !<105 REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) :: local_pf !< 103 106 104 107 -
palm/trunk/SOURCE/uv_exposure_model_mod.f90
r3004 r3014 25 25 ! ----------------- 26 26 ! $Id$ 27 ! Bugfix: domain bounds of local_pf corrected 28 ! 29 ! 3004 2018-04-27 12:33:25Z Giersch 27 30 ! Further allocation checks implemented (averaged data will be assigned to fill 28 31 ! values if no allocation happened so far) … … 337 340 REAL(wp) :: fill_value = -999.0_wp !< value for the _FillValue attribute 338 341 339 REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb :nzt+1) :: local_pf !<342 REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) :: local_pf !< 340 343 341 344
Note: See TracChangeset
for help on using the changeset viewer.