source: palm/trunk/SOURCE/plant_canopy_model_mod.f90 @ 4768

Last change on this file since 4768 was 4768, checked in by suehring, 3 years ago

Enable 3D data output also with 64-bit precision

  • Property svn:keywords set to Id
File size: 118.0 KB
Line 
1!> @file plant_canopy_model_mod.f90
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2020 Leibniz Universitaet Hannover
18! Copyright 2017-2020 Institute of Computer Science of the
19!                     Czech Academy of Sciences, Prague
20!------------------------------------------------------------------------------!
21!
22! Current revisions:
23! ------------------
24!
25!
26! Former revisions:
27! -----------------
28! $Id: plant_canopy_model_mod.f90 4768 2020-11-02 19:11:23Z suehring $
29! Enable 3D data output also with 64-bit precision
30!
31! 4671 2020-09-09 20:27:58Z pavelkrc
32! Implementation of downward facing USM and LSM surfaces
33!
34! 4535 2020-05-15 12:07:23Z raasch
35! bugfix for restart data format query
36!
37! 4525 2020-05-10 17:05:07Z raasch
38! bugfix for reading/writing pcm_...rate_av with MPI-IO
39!
40! 4517 2020-05-03 14:29:30Z raasch
41! added restart with MPI-IO for reading local arrays
42!
43! 4515 2020-04-30 16:37:18Z suehring
44! Rename error number again since this was recently given in -r 4511
45!
46! 4514 2020-04-30 16:29:59Z suehring
47! - Bugfix in output of pcm_heatrate_av in a restart run. In order to fix this,
48!   pch_index is now output for a restart run. Therefore, define global restart
49!   routines.
50! - Error message number renamed and check for PA0505 revised in order to also
51!   consider natural surfaces with plant-canopy.
52!
53! 4495 2020-04-13 20:11:20Z raasch
54! restart data handling with MPI-IO added
55!
56! 4457 2020-03-11 14:20:43Z raasch
57!
58! use statement for exchange horiz added
59! (salim) removed the error message PA0672 to consider PC 3d data via ascii file
60!
61! 4392 2020-01-31 16:14:57Z pavelkrc (resler)
62! Make pcm_heatrate_av, pcm_latentrate_av public to allow calculation
63! of averaged Bowen ratio in the user procedure
64!
65! 4381 2020-01-20 13:51:46Z suehring
66! Give error message 313 only once
67!
68! 4363 2020-01-07 18:11:28Z suehring
69! Fix for last commit
70!
71! 4362 2020-01-07 17:15:02Z suehring
72! Input of plant canopy variables from static driver moved to plant-canopy
73! model
74!
75! 4361 2020-01-07 12:22:38Z suehring
76! - Remove unused arrays in pmc_rrd_local
77! - Remove one exchange of ghost points
78!
79! 4360 2020-01-07 11:25:50Z suehring
80! - Bugfix, read restart data for time-averaged pcm output quantities
81! - Output of plant-canopy quantities will fill values
82!
83! 4356 2019-12-20 17:09:33Z suehring
84! Correct single message call, local check must be given by the respective
85! mpi rank.
86!
87! 4346 2019-12-18 11:55:56Z motisi
88! Introduction of wall_flags_total_0, which currently sets bits based on static
89! topography information used in wall_flags_static_0
90!
91! 4342 2019-12-16 13:49:14Z Giersch
92! Use statements moved to module level, ocean dependency removed, redundant
93! variables removed
94!
95! 4341 2019-12-16 10:43:49Z motisi
96! - Unification of variable names: pc_-variables now pcm_-variables
97!   (pc_latent_rate, pc_heating_rate, pc_transpiration_rate)
98! - Removal of pcm_bowenratio output
99! - Renamed canopy-mode 'block' to 'homogeneous'
100! - Renamed value 'read_from_file_3d' to 'read_from_file'
101! - Removal of confusing comment lines
102! - Replacement of k_wall by topo_top_ind
103! - Removal of Else-Statement in tendency-calculation
104!
105! 4335 2019-12-12 16:39:05Z suehring
106! Fix for LAD at building edges also implemented in vector branch.
107!
108! 4331 2019-12-10 18:25:02Z suehring
109! Typo corrected
110!
111! 4329 2019-12-10 15:46:36Z motisi
112! Renamed wall_flags_0 to wall_flags_static_0
113!
114! 4314 2019-11-29 10:29:20Z suehring
115! - Bugfix, plant canopy was still considered at building edges on for the u-
116!   and v-component.
117! - Relax restriction of LAD on building tops. LAD is only omitted at
118!   locations where building grid points emerged artificially by the
119!   topography filtering.
120!
121! 4309 2019-11-26 18:49:59Z suehring
122! Typo
123!
124! 4302 2019-11-22 13:15:56Z suehring
125! Omit tall canopy mapped on top of buildings
126!
127! 4279 2019-10-29 08:48:17Z scharf
128! unused variables removed
129!
130! 4258 2019-10-07 13:29:08Z scharf
131! changed check for static driver and fixed bugs in initialization and header
132!
133! 4258 2019-10-07 13:29:08Z suehring
134! Check if any LAD is prescribed when plant-canopy model is applied.
135!
136! 4226 2019-09-10 17:03:24Z suehring
137! Bugfix, missing initialization of heating rate
138!
139! 4221 2019-09-09 08:50:35Z suehring
140! Further bugfix in 3d data output for plant canopy
141!
142! 4216 2019-09-04 09:09:03Z suehring
143! Bugfixes in 3d data output
144!
145! 4205 2019-08-30 13:25:00Z suehring
146! Missing working precision + bugfix in calculation of wind speed
147!
148! 4188 2019-08-26 14:15:47Z suehring
149! Minor adjustment in error number
150!
151! 4187 2019-08-26 12:43:15Z suehring
152! Give specific error numbers instead of PA0999
153!
154! 4182 2019-08-22 15:20:23Z scharf
155! Corrected "Former revisions" section
156!
157! 4168 2019-08-16 13:50:17Z suehring
158! Replace function get_topography_top_index by topo_top_ind
159!
160! 4127 2019-07-30 14:47:10Z suehring
161! Output of 3D plant canopy variables changed. It is now relative to the local
162! terrain rather than located at the acutal vertical level in the model. This
163! way, the vertical dimension of the output can be significantly reduced.
164! (merge from branch resler)
165!
166! 3885 2019-04-11 11:29:34Z kanani
167! Changes related to global restructuring of location messages and introduction
168! of additional debug messages
169!
170! 3864 2019-04-05 09:01:56Z monakurppa
171! unsed variables removed
172!
173! 3745 2019-02-15 18:57:56Z suehring
174! Bugfix in transpiration, floating invalid when temperature
175! becomes > 40 degrees
176!
177! 3744 2019-02-15 18:38:58Z suehring
178! Some interface calls moved to module_interface + cleanup
179!
180! 3655 2019-01-07 16:51:22Z knoop
181! unused variables removed
182!
183! 138 2007-11-28 10:03:58Z letzel
184! Initial revision
185!
186! Description:
187! ------------
188!> 1) Initialization of the canopy model, e.g. construction of leaf area density
189!> profile (subroutine pcm_init).
190!> 2) Calculation of sinks and sources of momentum, heat and scalar concentration
191!> due to canopy elements (subroutine pcm_tendency).
192!
193! @todo - precalculate constant terms in pcm_calc_transpiration_rate
194! @todo - unify variable names (pcm_, pc_, ...)
195! @todo - get rid-off dependency on radiation model
196!------------------------------------------------------------------------------!
197 MODULE plant_canopy_model_mod
198
199    USE arrays_3d,                                                             &
200        ONLY:  dzu, dzw, e, exner, hyp, pt, q, s, tend, u, v, w, zu, zw
201
202    USE basic_constants_and_equations_mod,                                     &
203        ONLY:  c_p, degc_to_k, l_v, lv_d_cp, r_d, rd_d_rv
204
205    USE bulk_cloud_model_mod,                                                  &
206        ONLY: bulk_cloud_model, microphysics_seifert
207
208    USE control_parameters,                                                    &
209        ONLY: average_count_3d,                                                &
210              coupling_char,                                                   &
211              debug_output,                                                    &
212              dt_3d,                                                           &
213              dz,                                                              &
214              humidity,                                                        &
215              land_surface,                                                    &
216              length,                                                          &
217              message_string,                                                  &
218              ocean_mode,                                                      &
219              passive_scalar,                                                  &
220              plant_canopy,                                                    &
221              restart_data_format_output,                                      &
222              restart_string,                                                  &
223              urban_surface
224
225    USE grid_variables,                                                        &
226        ONLY:  dx, dy
227
228    USE indices,                                                               &
229        ONLY:  nbgp, nxl, nxlg, nxlu, nxr, nxrg, nyn, nyng, nys, nysg, nysv,   &
230               nz, nzb, nzt, topo_top_ind, wall_flags_total_0
231
232    USE kinds
233
234    USE netcdf_data_input_mod,                                                 &
235        ONLY:  input_pids_static,                                              &
236               char_fill,                                                      &
237               check_existence,                                                &
238               close_input_file,                                               &
239               get_attribute,                                                  &
240               get_dimension_length,                                           &
241               get_variable,                                                   &
242               inquire_num_variables,                                          &
243               inquire_variable_names,                                         &
244               input_file_static,                                              &
245               num_var_pids,                                                   &
246               open_read_file,                                                 &
247               pids_id,                                                        &
248               real_3d,                                                        &
249               vars_pids
250
251    USE pegrid
252
253    USE restart_data_mpi_io_mod,                                                                   &
254        ONLY:  rd_mpi_io_check_array,                                                              &
255               rrd_mpi_io,                                                                         &
256               wrd_mpi_io
257
258    USE surface_mod,                                                           &
259        ONLY: surf_def_h, surf_lsm_h, surf_usm_h
260
261
262    IMPLICIT NONE
263
264    CHARACTER (LEN=30)   ::  canopy_mode = 'homogeneous'           !< canopy coverage
265    LOGICAL              ::  plant_canopy_transpiration = .FALSE.  !< flag to switch calculation of transpiration and corresponding latent heat
266                                                                   !< for resolved plant canopy inside radiation model
267                                                                   !< (calls subroutine pcm_calc_transpiration_rate from module plant_canopy_mod)
268
269    INTEGER(iwp) ::  pch_index = 0                                 !< plant canopy height/top index
270    INTEGER(iwp) ::  lad_vertical_gradient_level_ind(10) = -9999   !< lad-profile levels (index)
271
272    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  pch_index_ji     !< local plant canopy top
273
274    LOGICAL ::  calc_beta_lad_profile = .FALSE.   !< switch for calc. of lad from beta func.
275
276    REAL(wp) ::  alpha_lad = 9999999.9_wp         !< coefficient for lad calculation
277    REAL(wp) ::  beta_lad = 9999999.9_wp          !< coefficient for lad calculation
278    REAL(wp) ::  canopy_drag_coeff = 0.0_wp       !< canopy drag coefficient (parameter)
279    REAL(wp) ::  cthf = 0.0_wp                    !< canopy top heat flux
280    REAL(wp) ::  dt_plant_canopy = 0.0_wp         !< timestep account. for canopy drag
281    REAL(wp) ::  ext_coef = 0.6_wp                !< extinction coefficient
282    REAL(wp) ::  lad_surface = 0.0_wp             !< lad surface value
283    REAL(wp) ::  lai_beta = 0.0_wp                !< leaf area index (lai) for lad calc.
284    REAL(wp) ::  leaf_scalar_exch_coeff = 0.0_wp  !< canopy scalar exchange coeff.
285    REAL(wp) ::  leaf_surface_conc = 0.0_wp       !< leaf surface concentration
286
287    REAL(wp) ::  lad_vertical_gradient(10) = 0.0_wp              !< lad gradient
288    REAL(wp) ::  lad_vertical_gradient_level(10) = -9999999.9_wp !< lad-prof. levels (in m)
289
290    REAL(wp) ::  lad_type_coef(0:10) = 1.0_wp   !< multiplicative coeficients for particular types
291                                                !< of plant canopy (e.g. deciduous tree during winter)
292
293    REAL(wp), DIMENSION(:), ALLOCATABLE ::  lad            !< leaf area density
294    REAL(wp), DIMENSION(:), ALLOCATABLE ::  pre_lad        !< preliminary lad
295   
296    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  cum_lai_hf               !< cumulative lai for heatflux calc.
297    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  lad_s                    !< lad on scalar-grid
298    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pcm_heating_rate         !< plant canopy heating rate
299    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pcm_transpiration_rate   !< plant canopy transpiration rate
300    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pcm_latent_rate          !< plant canopy latent heating rate
301
302    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pcm_heatrate_av          !< array for averaging plant canopy sensible heating rate
303    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pcm_latentrate_av        !< array for averaging plant canopy latent heating rate
304    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pcm_transpirationrate_av !< array for averaging plant canopy transpiration rate
305
306    TYPE(real_3d) ::  basal_area_density_f    !< input variable for basal area density - resolved vegetation
307    TYPE(real_3d) ::  leaf_area_density_f     !< input variable for leaf area density - resolved vegetation
308    TYPE(real_3d) ::  root_area_density_lad_f !< input variable for root area density - resolved vegetation
309
310    SAVE
311
312    PRIVATE
313   
314!
315!-- Public functions
316    PUBLIC pcm_calc_transpiration_rate,                                       &
317           pcm_check_data_output,                                             &
318           pcm_check_parameters,                                              &
319           pcm_3d_data_averaging,                                             &
320           pcm_data_output_3d,                                                &
321           pcm_define_netcdf_grid,                                            &
322           pcm_header,                                                        &
323           pcm_init,                                                          &
324           pcm_parin,                                                         &
325           pcm_rrd_global,                                                    &
326           pcm_rrd_local,                                                     &
327           pcm_tendency,                                                      &
328           pcm_wrd_global,                                                    &
329           pcm_wrd_local
330
331!
332!-- Public variables and constants
333    PUBLIC canopy_drag_coeff, pcm_heating_rate, pcm_transpiration_rate,       &
334           pcm_latent_rate, canopy_mode, cthf, dt_plant_canopy, lad, lad_s,   &
335           pch_index, plant_canopy_transpiration,                             &
336           pcm_heatrate_av, pcm_latentrate_av
337
338    INTERFACE pcm_calc_transpiration_rate
339       MODULE PROCEDURE pcm_calc_transpiration_rate
340    END INTERFACE pcm_calc_transpiration_rate
341
342    INTERFACE pcm_check_data_output
343       MODULE PROCEDURE pcm_check_data_output
344    END INTERFACE pcm_check_data_output
345   
346    INTERFACE pcm_check_parameters
347       MODULE PROCEDURE pcm_check_parameters
348    END INTERFACE pcm_check_parameters
349
350    INTERFACE pcm_3d_data_averaging
351       MODULE PROCEDURE pcm_3d_data_averaging
352    END INTERFACE pcm_3d_data_averaging
353
354    INTERFACE pcm_data_output_3d
355       MODULE PROCEDURE pcm_data_output_3d
356    END INTERFACE pcm_data_output_3d
357
358    INTERFACE pcm_define_netcdf_grid
359       MODULE PROCEDURE pcm_define_netcdf_grid
360    END INTERFACE pcm_define_netcdf_grid
361   
362     INTERFACE pcm_header
363       MODULE PROCEDURE pcm_header
364    END INTERFACE pcm_header       
365   
366    INTERFACE pcm_init
367       MODULE PROCEDURE pcm_init
368    END INTERFACE pcm_init
369
370    INTERFACE pcm_parin
371       MODULE PROCEDURE pcm_parin
372    END INTERFACE pcm_parin
373
374    INTERFACE pcm_read_plant_canopy_3d
375       MODULE PROCEDURE pcm_read_plant_canopy_3d
376    END INTERFACE pcm_read_plant_canopy_3d
377
378    INTERFACE pcm_rrd_local
379       MODULE PROCEDURE pcm_rrd_local_ftn
380       MODULE PROCEDURE pcm_rrd_local_mpi
381    END INTERFACE pcm_rrd_local
382
383    INTERFACE pcm_rrd_global
384       MODULE PROCEDURE pcm_rrd_global_ftn
385       MODULE PROCEDURE pcm_rrd_global_mpi
386    END INTERFACE pcm_rrd_global
387
388    INTERFACE pcm_tendency
389       MODULE PROCEDURE pcm_tendency
390       MODULE PROCEDURE pcm_tendency_ij
391    END INTERFACE pcm_tendency
392
393    INTERFACE pcm_wrd_local
394       MODULE PROCEDURE pcm_wrd_local
395    END INTERFACE pcm_wrd_local
396
397    INTERFACE pcm_wrd_global
398       MODULE PROCEDURE pcm_wrd_global
399    END INTERFACE pcm_wrd_global
400
401
402 CONTAINS
403 
404 
405!------------------------------------------------------------------------------!
406! Description:
407! ------------
408!> Calculation of the plant canopy transpiration rate based on the Jarvis-Stewart
409!> with parametrizations described in Daudet et al. (1999; Agricult. and Forest
410!> Meteorol. 97) and Ngao, Adam and Saudreau (2017;  Agricult. and Forest Meteorol
411!> 237-238). Model functions f1-f4 were adapted from Stewart (1998; Agric.
412!> and Forest. Meteorol. 43) instead, because they are valid for broader intervals
413!> of values. Funcion f4 used in form present in van Wijk et al. (1998;
414!> Tree Physiology 20).
415!>
416!> This subroutine is called from subroutine radiation_interaction
417!> after the calculation of radiation in plant canopy boxes.
418!> (arrays pcbinsw and pcbinlw).
419!>
420!------------------------------------------------------------------------------!
421 SUBROUTINE pcm_calc_transpiration_rate(i, j, k, kk, pcbsw, pcblw, pcbtr, pcblh)
422
423!
424!--  input parameters
425     INTEGER(iwp), INTENT(IN) ::  i, j, k, kk        !< indices of the pc gridbox
426     REAL(wp), INTENT(IN)     ::  pcbsw              !< sw radiation in gridbox (W)
427     REAL(wp), INTENT(IN)     ::  pcblw              !< lw radiation in gridbox (W)
428     REAL(wp), INTENT(OUT)    ::  pcbtr              !< transpiration rate dq/dt (kg/kg/s)
429     REAL(wp), INTENT(OUT)    ::  pcblh              !< latent heat from transpiration dT/dt (K/s)
430
431!--  variables and parameters for calculation of transpiration rate
432     REAL(wp)             ::  sat_press, sat_press_d, temp, v_lad
433     REAL(wp)             ::  d_fact, g_b, g_s, wind_speed, evapor_rate
434     REAL(wp)             ::  f1, f2, f3, f4, vpd, rswc, e_eq, e_imp, rad
435     REAL(wp), PARAMETER  ::  gama_psychr = 66.0_wp !< psychrometric constant (Pa/K)
436     REAL(wp), PARAMETER  ::  g_s_max = 0.01        !< maximum stomatal conductivity (m/s)
437     REAL(wp), PARAMETER  ::  m_soil = 0.4_wp       !< soil water content (needs to adjust or take from LSM)
438     REAL(wp), PARAMETER  ::  m_wilt = 0.01_wp      !< wilting point soil water content (needs to adjust or take from LSM)
439     REAL(wp), PARAMETER  ::  m_sat = 0.51_wp       !< saturation soil water content (needs to adjust or take from LSM)
440     REAL(wp), PARAMETER  ::  t2_min = 0.0_wp       !< minimal temperature for calculation of f2
441     REAL(wp), PARAMETER  ::  t2_max = 40.0_wp      !< maximal temperature for calculation of f2
442
443
444!--  Temperature (deg C)
445     temp = pt(k,j,i) * exner(k) - degc_to_k
446!--  Coefficient for conversion of radiation to grid to radiation to unit leaves surface
447     v_lad = 1.0_wp / ( MAX( lad_s(kk,j,i), 1.0E-10_wp ) * dx * dy * dz(1) )
448!--  Magnus formula for the saturation pressure (see Ngao, Adam and Saudreau (2017) eq. 1)
449!--  There are updated formulas available, kept consistent with the rest of the parametrization
450     sat_press = 610.8_wp * exp(17.27_wp * temp/(temp + 237.3_wp))
451!--  Saturation pressure derivative (derivative of the above)
452     sat_press_d = sat_press * 17.27_wp * 237.3_wp / (temp + 237.3_wp)**2
453!--  Wind speed
454     wind_speed = SQRT( ( 0.5_wp * ( u(k,j,i) + u(k,j,i+1) ) )**2 +            &
455                        ( 0.5_wp * ( v(k,j,i) + v(k,j+1,i) ) )**2 +            &
456                        ( 0.5_wp * ( w(k,j,i) + w(k-1,j,i) ) )**2 )
457!--  Aerodynamic conductivity (Daudet et al. (1999) eq. 14
458     g_b = 0.01_wp * wind_speed + 0.0071_wp
459!--  Radiation flux per leaf surface unit
460     rad = pcbsw * v_lad
461!--  First function for calculation of stomatal conductivity (radiation dependency)
462!--  Stewart (1988; Agric. and Forest. Meteorol. 43) eq. 17
463     f1 = rad * (1000.0_wp+42.1_wp) / 1000.0_wp / (rad+42.1_wp)
464!--  Second function for calculation of stomatal conductivity (temperature dependency)
465!--  Stewart (1988; Agric. and Forest. Meteorol. 43) eq. 21
466     f2 = MAX(t2_min, (temp-t2_min) * MAX(0.0_wp,t2_max-temp)**((t2_max-16.9_wp)/(16.9_wp-t2_min)) / &
467              ((16.9_wp-t2_min) * (t2_max-16.9_wp)**((t2_max-16.9_wp)/(16.9_wp-t2_min))) )
468!--  Water pressure deficit
469!--  Ngao, Adam and Saudreau (2017) eq. 6 but with water vapour partial pressure
470     vpd = max( sat_press - q(k,j,i) * hyp(k) / rd_d_rv, 0._wp )
471!--  Third function for calculation of stomatal conductivity (water pressure deficit dependency)
472!--  Ngao, Adam and Saudreau (2017) Table 1, limited from below according to Stewart (1988)
473!--  The coefficients of the linear dependence should better correspond to broad-leaved trees
474!--  than the coefficients from Stewart (1988) which correspond to conifer trees.
475     vpd = MIN(MAX(vpd,770.0_wp),3820.0_wp)
476     f3 = -2E-4_wp * vpd + 1.154_wp
477!--  Fourth function for calculation of stomatal conductivity (soil moisture dependency)
478!--  Residual soil water content
479!--  van Wijk et al. (1998; Tree Physiology 20) eq. 7
480!--  TODO - over LSM surface might be calculated from LSM parameters
481     rswc = ( m_sat - m_soil ) / ( m_sat - m_wilt )
482!--  van Wijk et al. (1998; Tree Physiology 20) eq. 5-6 (it is a reformulation of eq. 22-23 of Stewart(1988))
483     f4 = MAX(0.0_wp, MIN(1.0_wp - 0.041_wp * EXP(3.2_wp * rswc), 1.0_wp - 0.041_wp))
484!--  Stomatal conductivity
485!--  Stewart (1988; Agric. and Forest. Meteorol. 43) eq. 12
486!--  (notation according to Ngao, Adam and Saudreau (2017) and others)
487     g_s = g_s_max * f1 * f2 * f3 * f4 + 1.0E-10_wp
488!--  Decoupling factor
489!--  Daudet et al. (1999) eq. 6
490     d_fact = (sat_press_d / gama_psychr + 2.0_wp ) /                        &
491              (sat_press_d / gama_psychr + 2.0_wp + 2.0_wp * g_b / g_s )
492!--  Equilibrium evaporation rate
493!--  Daudet et al. (1999) eq. 4
494     e_eq = (pcbsw + pcblw) * v_lad * sat_press_d /                         &
495                 gama_psychr /( sat_press_d / gama_psychr + 2.0_wp ) / l_v
496!--  Imposed evaporation rate
497!--  Daudet et al. (1999) eq. 5
498     e_imp = r_d * pt(k,j,i) * exner(k) / hyp(k) * c_p * g_s * vpd / gama_psychr / l_v
499!--  Evaporation rate
500!--  Daudet et al. (1999) eq. 3
501!--  (evaporation rate is limited to non-negative values)
502     evapor_rate = MAX(d_fact * e_eq + ( 1.0_wp - d_fact ) * e_imp, 0.0_wp)
503!--  Conversion of evaporation rate to q tendency in gridbox
504!--  dq/dt = E * LAD * V_g / (rho_air * V_g)
505     pcbtr = evapor_rate * r_d * pt(k,j,i) * exner(k) * lad_s(kk,j,i) / hyp(k)  !-- = dq/dt
506!--  latent heat from evaporation
507     pcblh = pcbtr * lv_d_cp  !-- = - dT/dt
508
509 END SUBROUTINE pcm_calc_transpiration_rate
510
511
512!------------------------------------------------------------------------------!
513! Description:
514! ------------
515!> Check data output for plant canopy model
516!------------------------------------------------------------------------------!
517 SUBROUTINE pcm_check_data_output( var, unit )
518
519    CHARACTER (LEN=*) ::  unit  !<
520    CHARACTER (LEN=*) ::  var   !<
521
522
523    SELECT CASE ( TRIM( var ) )
524
525       CASE ( 'pcm_heatrate' )
526!
527!--       Output of heatrate can be only done if it is explicitely set by cthf,
528!--       or parametrized by absorption of radiation. The latter, however, is
529!--       only available if radiation_interactions are on. Note, these are
530!--       enabled if land-surface or urban-surface is switched-on. Using
531!--       radiation_interactions_on directly is not possible since it belongs
532!--       to the radition_model, which in turn depends on the plant-canopy model,
533!--       creating circular dependencies.
534          IF ( cthf == 0.0_wp  .AND. (  .NOT.  urban_surface  .AND.             &
535                                        .NOT.  land_surface ) )  THEN
536             message_string = 'output of "' // TRIM( var ) // '" requi' //      &
537                              'res setting of parameter cthf /= 0.0'
538             CALL message( 'pcm_check_data_output', 'PA0718', 1, 2, 0, 6, 0 )
539          ENDIF
540          unit = 'K s-1'
541   
542       CASE ( 'pcm_transpirationrate' )
543          unit = 'kg kg-1 s-1'
544
545       CASE ( 'pcm_latentrate' )
546          unit = 'K s-1'
547
548       CASE ( 'pcm_lad' )
549          unit = 'm2 m-3'
550
551
552       CASE DEFAULT
553          unit = 'illegal'
554
555    END SELECT
556
557
558 END SUBROUTINE pcm_check_data_output
559 
560 
561!------------------------------------------------------------------------------!
562! Description:
563! ------------
564!> Check parameters routine for plant canopy model
565!------------------------------------------------------------------------------!
566    SUBROUTINE pcm_check_parameters
567           
568       IF ( ocean_mode )  THEN
569          message_string = 'plant_canopy = .TRUE. is not allowed in the '//    &
570                           'ocean'
571          CALL message( 'pcm_check_parameters', 'PA0696', 1, 2, 0, 6, 0 )
572       ENDIF
573           
574       IF ( canopy_drag_coeff == 0.0_wp )  THEN
575          message_string = 'plant_canopy = .TRUE. requires a non-zero drag '// &
576                           'coefficient & given value is canopy_drag_coeff = 0.0'
577          CALL message( 'pcm_check_parameters', 'PA0041', 1, 2, 0, 6, 0 )
578       ENDIF
579
580       IF ( ( alpha_lad /= 9999999.9_wp  .AND.  beta_lad == 9999999.9_wp ) .OR.&
581              beta_lad /= 9999999.9_wp   .AND.  alpha_lad == 9999999.9_wp )  THEN
582          message_string = 'using the beta function for the construction ' //  &
583                           'of the leaf area density profile requires '    //  &
584                           'both alpha_lad and beta_lad to be /= 9999999.9'
585          CALL message( 'pcm_check_parameters', 'PA0118', 1, 2, 0, 6, 0 )
586       ENDIF
587
588       IF ( calc_beta_lad_profile  .AND.  lai_beta == 0.0_wp )  THEN
589          message_string = 'using the beta function for the construction ' //  &
590                           'of the leaf area density profile requires '    //  &
591                           'a non-zero lai_beta, but given value is '      //  &
592                           'lai_beta = 0.0'
593          CALL message( 'pcm_check_parameters', 'PA0119', 1, 2, 0, 6, 0 )
594       ENDIF
595
596       IF ( calc_beta_lad_profile  .AND.  lad_surface /= 0.0_wp )  THEN
597          message_string = 'simultaneous setting of alpha_lad /= 9999999.9 '// &
598                           'combined with beta_lad /= 9999999.9 '           // &
599                           'and lad_surface /= 0.0 is not possible, '       // &
600                           'use either vertical gradients or the beta '     // &
601                           'function for the construction of the leaf area '// &
602                           'density profile'
603          CALL message( 'pcm_check_parameters', 'PA0120', 1, 2, 0, 6, 0 )
604       ENDIF
605
606       IF ( bulk_cloud_model  .AND.  microphysics_seifert )  THEN
607          message_string = 'plant_canopy = .TRUE. requires cloud_scheme /=' // &
608                          ' seifert_beheng'
609          CALL message( 'pcm_check_parameters', 'PA0360', 1, 2, 0, 6, 0 )
610       ENDIF
611
612    END SUBROUTINE pcm_check_parameters 
613 
614
615!------------------------------------------------------------------------------!
616!
617! Description:
618! ------------
619!> Subroutine for averaging 3D data
620!------------------------------------------------------------------------------!
621 SUBROUTINE pcm_3d_data_averaging( mode, variable )
622
623    CHARACTER (LEN=*) ::  mode    !<
624    CHARACTER (LEN=*) :: variable !<
625
626    INTEGER(iwp) ::  i            !<
627    INTEGER(iwp) ::  j            !<
628    INTEGER(iwp) ::  k            !<
629
630
631    IF ( mode == 'allocate' )  THEN
632
633       SELECT CASE ( TRIM( variable ) )
634
635          CASE ( 'pcm_heatrate' )
636             IF ( .NOT. ALLOCATED( pcm_heatrate_av ) )  THEN
637                ALLOCATE( pcm_heatrate_av(0:pch_index,nysg:nyng,nxlg:nxrg) )
638             ENDIF
639             pcm_heatrate_av = 0.0_wp
640
641
642          CASE ( 'pcm_latentrate' )
643             IF ( .NOT. ALLOCATED( pcm_latentrate_av ) )  THEN
644                ALLOCATE( pcm_latentrate_av(0:pch_index,nysg:nyng,nxlg:nxrg) )
645             ENDIF
646             pcm_latentrate_av = 0.0_wp
647
648
649          CASE ( 'pcm_transpirationrate' )
650             IF ( .NOT. ALLOCATED( pcm_transpirationrate_av ) )  THEN
651                ALLOCATE( pcm_transpirationrate_av(0:pch_index,nysg:nyng,nxlg:nxrg) )
652             ENDIF
653             pcm_transpirationrate_av = 0.0_wp
654
655          CASE DEFAULT
656             CONTINUE
657
658       END SELECT
659
660    ELSEIF ( mode == 'sum' )  THEN
661
662       SELECT CASE ( TRIM( variable ) )
663
664          CASE ( 'pcm_heatrate' )
665             IF ( ALLOCATED( pcm_heatrate_av ) ) THEN
666                DO  i = nxl, nxr
667                   DO  j = nys, nyn
668                      IF ( pch_index_ji(j,i) /= 0 )  THEN
669                         DO  k = 0, pch_index_ji(j,i)
670                            pcm_heatrate_av(k,j,i) = pcm_heatrate_av(k,j,i) + pcm_heating_rate(k,j,i)
671                         ENDDO
672                      ENDIF
673                   ENDDO
674                ENDDO
675             ENDIF
676
677
678          CASE ( 'pcm_latentrate' )
679             IF ( ALLOCATED( pcm_latentrate_av ) ) THEN
680                DO  i = nxl, nxr
681                   DO  j = nys, nyn
682                      IF ( pch_index_ji(j,i) /= 0 )  THEN
683                         DO  k = 0, pch_index_ji(j,i)
684                            pcm_latentrate_av(k,j,i) = pcm_latentrate_av(k,j,i) + pcm_latent_rate(k,j,i)
685                         ENDDO
686                      ENDIF
687                   ENDDO
688                ENDDO
689             ENDIF
690
691
692          CASE ( 'pcm_transpirationrate' )
693             IF ( ALLOCATED( pcm_transpirationrate_av ) ) THEN
694                DO  i = nxl, nxr
695                   DO  j = nys, nyn
696                      IF ( pch_index_ji(j,i) /= 0 )  THEN
697                         DO  k = 0, pch_index_ji(j,i)
698                            pcm_transpirationrate_av(k,j,i) = pcm_transpirationrate_av(k,j,i) + pcm_transpiration_rate(k,j,i)
699                         ENDDO
700                      ENDIF
701                   ENDDO
702                ENDDO
703             ENDIF
704
705          CASE DEFAULT
706             CONTINUE
707
708       END SELECT
709
710    ELSEIF ( mode == 'average' )  THEN
711
712       SELECT CASE ( TRIM( variable ) )
713
714          CASE ( 'pcm_heatrate' )
715             IF ( ALLOCATED( pcm_heatrate_av ) ) THEN
716                DO  i = nxlg, nxrg
717                   DO  j = nysg, nyng
718                      IF ( pch_index_ji(j,i) /= 0 )  THEN
719                         DO  k = 0, pch_index_ji(j,i)
720                            pcm_heatrate_av(k,j,i) = pcm_heatrate_av(k,j,i)                 &
721                                                     / REAL( average_count_3d, KIND=wp )
722                         ENDDO
723                      ENDIF
724                   ENDDO
725                ENDDO
726             ENDIF
727
728
729          CASE ( 'pcm_latentrate' )
730             IF ( ALLOCATED( pcm_latentrate_av ) ) THEN
731                DO  i = nxlg, nxrg
732                   DO  j = nysg, nyng
733                      IF ( pch_index_ji(j,i) /= 0 )  THEN
734                         DO  k = 0, pch_index_ji(j,i)
735                            pcm_latentrate_av(k,j,i) = pcm_latentrate_av(k,j,i)              &
736                                                       / REAL( average_count_3d, KIND=wp )
737                         ENDDO
738                      ENDIF
739                   ENDDO
740                ENDDO
741             ENDIF
742
743
744          CASE ( 'pcm_transpirationrate' )
745             IF ( ALLOCATED( pcm_transpirationrate_av ) ) THEN
746                DO  i = nxlg, nxrg
747                   DO  j = nysg, nyng
748                      IF ( pch_index_ji(j,i) /= 0 )  THEN
749                         DO  k = 0, pch_index_ji(j,i)
750                            pcm_transpirationrate_av(k,j,i) = pcm_transpirationrate_av(k,j,i)  &
751                                                              / REAL( average_count_3d, KIND=wp )
752                         ENDDO
753                      ENDIF
754                   ENDDO
755                ENDDO
756             ENDIF
757
758       END SELECT
759
760    ENDIF
761
762 END SUBROUTINE pcm_3d_data_averaging
763
764!------------------------------------------------------------------------------!
765!
766! Description:
767! ------------
768!> Subroutine defining 3D output variables.
769!> Note, 3D plant-canopy output has it's own vertical output dimension, meaning
770!> that 3D output is relative to the model surface now rather than at the actual
771!> grid point where the plant canopy is located.
772!------------------------------------------------------------------------------!
773 SUBROUTINE pcm_data_output_3d( av, variable, found, local_pf, fill_value,     &
774                                nzb_do, nzt_do )
775
776    CHARACTER (LEN=*) ::  variable !< treated variable
777
778    INTEGER(iwp) ::  av     !< flag indicating instantaneous or averaged data output
779    INTEGER(iwp) ::  i      !< grid index x-direction
780    INTEGER(iwp) ::  j      !< grid index y-direction
781    INTEGER(iwp) ::  k      !< grid index z-direction
782    INTEGER(iwp) ::  nzb_do !< lower limit of the data output (usually 0)
783    INTEGER(iwp) ::  nzt_do !< vertical upper limit of the data output (usually nz_do3d)
784
785    LOGICAL      ::  found  !< flag indicating if variable is found
786
787    REAL(wp)     ::  fill_value !< fill value
788    REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !< data output array
789
790
791    found = .TRUE.
792
793    local_pf = REAL( fill_value, KIND = 4 )
794
795    SELECT CASE ( TRIM( variable ) )
796!
797!--    Note, to save memory arrays for heating are allocated from 0:pch_index.
798!--    Thus, output must be relative to these array indices. Further, check
799!--    whether the output is within the vertical output range,
800!--    i.e. nzb_do:nzt_do, which is necessary as local_pf is only allocated
801!--    for this index space. Note, plant-canopy output has a separate
802!--    vertical output coordinate zlad, so that output is mapped down to the
803!--    surface.
804       CASE ( 'pcm_heatrate' )
805          IF ( av == 0 )  THEN
806             DO  i = nxl, nxr
807                DO  j = nys, nyn
808                   DO  k = MAX( 1, nzb_do ), MIN( pch_index_ji(j,i), nzt_do )
809                      local_pf(i,j,k) = pcm_heating_rate(k,j,i)
810                   ENDDO
811                ENDDO
812             ENDDO
813          ELSE
814             DO  i = nxl, nxr
815                DO  j = nys, nyn
816                   DO  k = MAX( 1, nzb_do ), MIN( pch_index_ji(j,i), nzt_do )
817                      local_pf(i,j,k) = pcm_heatrate_av(k,j,i)
818                   ENDDO
819                ENDDO
820             ENDDO
821          ENDIF
822
823       CASE ( 'pcm_latentrate' )
824          IF ( av == 0 )  THEN
825             DO  i = nxl, nxr
826                DO  j = nys, nyn
827                   DO  k = MAX( 1, nzb_do ), MIN( pch_index_ji(j,i), nzt_do )
828                      local_pf(i,j,k) = pcm_latent_rate(k,j,i)
829                   ENDDO
830                ENDDO
831             ENDDO
832          ELSE
833             DO  i = nxl, nxr
834                DO  j = nys, nyn
835                   DO  k = MAX( 1, nzb_do ), MIN( pch_index_ji(j,i), nzt_do )
836                      local_pf(i,j,k) = pcm_latentrate_av(k,j,i)
837                   ENDDO
838                ENDDO
839             ENDDO
840          ENDIF
841
842       CASE ( 'pcm_transpirationrate' )
843          IF ( av == 0 )  THEN
844             DO  i = nxl, nxr
845                DO  j = nys, nyn
846                   DO  k = MAX( 1, nzb_do ), MIN( pch_index_ji(j,i), nzt_do )
847                      local_pf(i,j,k) = pcm_transpiration_rate(k,j,i)
848                   ENDDO
849                ENDDO
850             ENDDO
851          ELSE
852             DO  i = nxl, nxr
853                DO  j = nys, nyn
854                   DO  k = MAX( 1, nzb_do ), MIN( pch_index_ji(j,i), nzt_do )
855                      local_pf(i,j,k) = pcm_transpirationrate_av(k,j,i)
856                   ENDDO
857                ENDDO
858             ENDDO
859          ENDIF
860
861       CASE ( 'pcm_lad' )
862          IF ( av == 0 )  THEN
863             DO  i = nxl, nxr
864                DO  j = nys, nyn
865                   DO  k = MAX( 1, nzb_do ), MIN( pch_index_ji(j,i), nzt_do )
866                      local_pf(i,j,k) = lad_s(k,j,i)
867                   ENDDO
868                ENDDO
869             ENDDO
870          ENDIF
871
872       CASE DEFAULT
873          found = .FALSE.
874
875    END SELECT
876
877 END SUBROUTINE pcm_data_output_3d 
878         
879!------------------------------------------------------------------------------!
880!
881! Description:
882! ------------
883!> Subroutine defining appropriate grid for netcdf variables.
884!> It is called from subroutine netcdf.
885!------------------------------------------------------------------------------!
886 SUBROUTINE pcm_define_netcdf_grid( var, found, grid_x, grid_y, grid_z )
887
888     CHARACTER (LEN=*), INTENT(IN)  ::  var         !<
889     LOGICAL, INTENT(OUT)           ::  found       !<
890     CHARACTER (LEN=*), INTENT(OUT) ::  grid_x      !<
891     CHARACTER (LEN=*), INTENT(OUT) ::  grid_y      !<
892     CHARACTER (LEN=*), INTENT(OUT) ::  grid_z      !<
893
894     found  = .TRUE.
895
896!
897!--  Check for the grid. zpc is zu(nzb:nzb+pch_index)
898     SELECT CASE ( TRIM( var ) )
899
900        CASE ( 'pcm_heatrate', 'pcm_lad', 'pcm_transpirationrate', 'pcm_latentrate')
901           grid_x = 'x'
902           grid_y = 'y'
903           grid_z = 'zpc'
904
905        CASE DEFAULT
906           found  = .FALSE.
907           grid_x = 'none'
908           grid_y = 'none'
909           grid_z = 'none'
910     END SELECT
911
912 END SUBROUTINE pcm_define_netcdf_grid
913 
914 
915!------------------------------------------------------------------------------!
916! Description:
917! ------------
918!> Header output for plant canopy model
919!------------------------------------------------------------------------------!
920 SUBROUTINE pcm_header ( io )
921 
922    CHARACTER (LEN=10) ::  coor_chr            !<
923
924    CHARACTER (LEN=86) ::  coordinates         !<
925    CHARACTER (LEN=86) ::  gradients           !<
926    CHARACTER (LEN=86) ::  leaf_area_density   !<
927    CHARACTER (LEN=86) ::  slices              !<
928 
929    INTEGER(iwp) :: i                !<
930    INTEGER(iwp),  INTENT(IN) ::  io !< Unit of the output file
931    INTEGER(iwp) :: k                !<       
932 
933    REAL(wp) ::  canopy_height       !< canopy height (in m)
934   
935    canopy_height = zw(pch_index)
936
937    WRITE ( io, 1 )  canopy_mode, canopy_height, pch_index,                    &
938                       canopy_drag_coeff                                       
939    IF ( passive_scalar )  THEN                                               
940       WRITE ( io, 2 )  leaf_scalar_exch_coeff,                                &
941                          leaf_surface_conc
942    ENDIF
943
944!
945!   Heat flux at the top of vegetation
946    WRITE ( io, 3 )  cthf
947
948!
949!   Leaf area density profile, calculated either from given vertical
950!   gradients or from beta probability density function.
951    IF (  .NOT.  calc_beta_lad_profile )  THEN
952
953!      Building output strings, starting with surface value
954       WRITE ( leaf_area_density, '(F7.4)' )  lad_surface
955       gradients = '------'
956       slices = '     0'
957       coordinates = '   0.0'
958       DO i = 1, UBOUND(lad_vertical_gradient_level_ind, DIM=1)
959          IF  ( lad_vertical_gradient_level_ind(i) /= -9999 ) THEN
960
961             WRITE (coor_chr,'(F7.2)') lad(lad_vertical_gradient_level_ind(i))
962             leaf_area_density = TRIM( leaf_area_density ) // ' ' // TRIM( coor_chr )
963
964             WRITE (coor_chr,'(F7.2)') lad_vertical_gradient(i)
965             gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
966
967             WRITE (coor_chr,'(I7)') lad_vertical_gradient_level_ind(i)
968             slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
969
970             WRITE (coor_chr,'(F7.1)') lad_vertical_gradient_level(i)
971             coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
972          ELSE
973             EXIT
974          ENDIF
975       ENDDO
976
977       WRITE ( io, 4 )  TRIM( coordinates ), TRIM( leaf_area_density ),        &
978                          TRIM( gradients ), TRIM( slices )
979
980    ELSE
981   
982       WRITE ( leaf_area_density, '(F7.4)' )  lad_surface
983       coordinates = '   0.0'
984       
985       DO  k = 1, pch_index
986
987          WRITE (coor_chr,'(F7.2)')  lad(k)
988          leaf_area_density = TRIM( leaf_area_density ) // ' ' //              &
989                              TRIM( coor_chr )                                 
990                                                                               
991          WRITE (coor_chr,'(F7.1)')  zu(k)                                     
992          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )       
993                                                                               
994       ENDDO                                                                   
995                                                                               
996       WRITE ( io, 5 ) TRIM( coordinates ), TRIM( leaf_area_density ),         &
997                       alpha_lad, beta_lad, lai_beta
998
999    ENDIF 
1000
10011   FORMAT (//' Vegetation canopy (drag) model:'/                              &
1002              ' ------------------------------'//                              &
1003              ' Canopy mode: ', A /                                            &
1004              ' Canopy height: ',F6.2,'m (',I4,' grid points)' /               &
1005              ' Leaf drag coefficient: ',F6.2 /)
10062   FORMAT (/ ' Scalar exchange coefficient: ',F6.2 /                          &
1007              ' Scalar concentration at leaf surfaces in kg/m**3: ',F6.2 /)
10083   FORMAT (' Predefined constant heatflux at the top of the vegetation: ',    &
1009             F6.2, ' K m/s')
10104   FORMAT (/ ' Characteristic levels of the leaf area density:'//             &
1011              ' Height:              ',A,'  m'/                                &
1012              ' Leaf area density:   ',A,'  m**2/m**3'/                        &
1013              ' Gradient:            ',A,'  m**2/m**4'/                        &
1014              ' Gridpoint:           ',A)
10155   FORMAT (//' Characteristic levels of the leaf area density and coefficients:'&
1016          //  ' Height:              ',A,'  m'/                                &
1017              ' Leaf area density:   ',A,'  m**2/m**3'/                        &
1018              ' Coefficient alpha: ',F6.2 /                                    &
1019              ' Coefficient beta: ',F6.2 /                                     &
1020              ' Leaf area index: ',F6.2,'  m**2/m**2' /)   
1021       
1022    END SUBROUTINE pcm_header
1023 
1024 
1025!------------------------------------------------------------------------------!
1026! Description:
1027! ------------
1028!> Initialization of the plant canopy model
1029!------------------------------------------------------------------------------!
1030    SUBROUTINE pcm_init
1031
1032       USE exchange_horiz_mod,                                                    &
1033           ONLY:  exchange_horiz
1034
1035       INTEGER(iwp) ::  i   !< running index
1036       INTEGER(iwp) ::  j   !< running index
1037       INTEGER(iwp) ::  k   !< running index
1038       INTEGER(iwp) ::  m   !< running index
1039
1040       LOGICAL      ::  lad_on_top = .FALSE.  !< dummy flag to indicate that LAD is defined on a building roof
1041
1042       REAL(wp) ::  canopy_height   !< canopy height for lad-profile construction
1043       REAL(wp) ::  gradient        !< gradient for lad-profile construction
1044       REAL(wp) ::  int_bpdf        !< vertical integral for lad-profile construction     
1045       REAL(wp) ::  lad_max         !< maximum LAD value in the model domain, used to perform a check
1046
1047       IF ( debug_output )  CALL debug_message( 'pcm_init', 'start' )
1048!
1049!--    Allocate one-dimensional arrays for the computation of the
1050!--    leaf area density (lad) profile
1051       ALLOCATE( lad(0:nz+1), pre_lad(0:nz+1) )
1052       lad = 0.0_wp
1053       pre_lad = 0.0_wp
1054
1055!
1056!--    Set flag that indicates that the lad-profile shall be calculated by using
1057!--    a beta probability density function
1058       IF ( alpha_lad /= 9999999.9_wp  .AND.  beta_lad /= 9999999.9_wp )  THEN
1059          calc_beta_lad_profile = .TRUE.
1060       ENDIF
1061       
1062       
1063!
1064!--    Compute the profile of leaf area density used in the plant
1065!--    canopy model. The profile can either be constructed from
1066!--    prescribed vertical gradients of the leaf area density or by
1067!--    using a beta probability density function (see e.g. Markkanen et al.,
1068!--    2003: Boundary-Layer Meteorology, 106, 437-459)
1069       IF (  .NOT.  calc_beta_lad_profile )  THEN   
1070
1071!
1072!--       Use vertical gradients for lad-profile construction   
1073          i = 1
1074          gradient = 0.0_wp
1075
1076          lad(0) = lad_surface
1077          lad_vertical_gradient_level_ind(1) = 0
1078
1079          DO k = 1, pch_index
1080             IF ( i < 11 )  THEN
1081                IF ( lad_vertical_gradient_level(i) < zu(k)  .AND.          &
1082                     lad_vertical_gradient_level(i) >= 0.0_wp )  THEN
1083                   gradient = lad_vertical_gradient(i)
1084                   lad_vertical_gradient_level_ind(i) = k - 1
1085                   i = i + 1
1086                ENDIF
1087             ENDIF
1088             IF ( gradient /= 0.0_wp )  THEN
1089                IF ( k /= 1 )  THEN
1090                   lad(k) = lad(k-1) + dzu(k) * gradient
1091                ELSE
1092                   lad(k) = lad_surface + dzu(k) * gradient
1093                ENDIF
1094             ELSE
1095                lad(k) = lad(k-1)
1096             ENDIF
1097          ENDDO
1098
1099!
1100!--       In case of no given leaf area density gradients, choose a vanishing
1101!--       gradient. This information is used for the HEADER and the RUN_CONTROL
1102!--       file.
1103          IF ( lad_vertical_gradient_level(1) == -9999999.9_wp )  THEN
1104             lad_vertical_gradient_level(1) = 0.0_wp
1105          ENDIF
1106
1107       ELSE
1108
1109!
1110!--       Use beta function for lad-profile construction
1111          int_bpdf = 0.0_wp
1112          canopy_height = zw(pch_index)
1113
1114          DO k = 0, pch_index
1115             int_bpdf = int_bpdf +                                             &
1116                      ( ( ( zw(k) / canopy_height )**( alpha_lad-1.0_wp ) ) *  &
1117                      ( ( 1.0_wp - ( zw(k) / canopy_height ) )**(              &
1118                          beta_lad-1.0_wp ) )                                  &
1119                      * ( ( zw(k+1)-zw(k) ) / canopy_height ) )
1120          ENDDO
1121
1122!
1123!--       Preliminary lad profile (defined on w-grid)
1124          DO k = 0, pch_index
1125             pre_lad(k) =  lai_beta *                                          &
1126                        ( ( ( zw(k) / canopy_height )**( alpha_lad-1.0_wp ) )  &
1127                        * ( ( 1.0_wp - ( zw(k) / canopy_height ) )**(          &
1128                              beta_lad-1.0_wp ) ) / int_bpdf                   &
1129                        ) / canopy_height
1130          ENDDO
1131
1132!
1133!--       Final lad profile (defined on scalar-grid level, since most prognostic
1134!--       quantities are defined there, hence, less interpolation is required
1135!--       when calculating the canopy tendencies)
1136          lad(0) = pre_lad(0)
1137          DO k = 1, pch_index
1138             lad(k) = 0.5 * ( pre_lad(k-1) + pre_lad(k) )
1139          ENDDO
1140
1141       ENDIF
1142
1143!
1144!--    Allocate 3D-array for the leaf area density (lad_s).
1145       ALLOCATE( lad_s(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1146
1147!
1148!--    Initialization of the canopy coverage in the model domain:
1149!--    Setting the parameter canopy_mode = 'homogeneous' initializes a canopy, which
1150!--    fully covers the domain surface
1151       SELECT CASE ( TRIM( canopy_mode ) )
1152
1153          CASE( 'homogeneous' )
1154
1155             DO  i = nxlg, nxrg
1156                DO  j = nysg, nyng
1157                   lad_s(:,j,i) = lad(:)
1158                ENDDO
1159             ENDDO
1160
1161          CASE ( 'read_from_file' )
1162!
1163!--          Read plant canopy
1164             IF ( input_pids_static )  THEN
1165!
1166!--             Open the static input file
1167#if defined( __netcdf )
1168                CALL open_read_file( TRIM( input_file_static ) //              &
1169                                     TRIM( coupling_char ),                    &
1170                                     pids_id )
1171
1172                CALL inquire_num_variables( pids_id, num_var_pids )
1173!
1174!--             Allocate memory to store variable names and read them
1175                ALLOCATE( vars_pids(1:num_var_pids) )
1176                CALL inquire_variable_names( pids_id, vars_pids )
1177!
1178!--             Read leaf area density - resolved vegetation
1179                IF ( check_existence( vars_pids, 'lad' ) )  THEN
1180                   leaf_area_density_f%from_file = .TRUE.
1181                   CALL get_attribute( pids_id, char_fill,                     &
1182                                       leaf_area_density_f%fill,               &
1183                                       .FALSE., 'lad' )
1184!
1185!--                Inquire number of vertical vegetation layer
1186                   CALL get_dimension_length( pids_id,                         &
1187                                              leaf_area_density_f%nz,          &
1188                                              'zlad' )
1189!
1190!--                Allocate variable for leaf-area density
1191                   ALLOCATE( leaf_area_density_f%var                           &
1192                                                (0:leaf_area_density_f%nz-1,   &
1193                                                 nys:nyn,nxl:nxr) )
1194
1195                   CALL get_variable( pids_id, 'lad', leaf_area_density_f%var, &
1196                                      nxl, nxr, nys, nyn,                      &
1197                                      0, leaf_area_density_f%nz-1 )
1198
1199                ELSE
1200                   leaf_area_density_f%from_file = .FALSE.
1201                ENDIF
1202!
1203!--             Read basal area density - resolved vegetation
1204                IF ( check_existence( vars_pids, 'bad' ) )  THEN
1205                   basal_area_density_f%from_file = .TRUE.
1206                   CALL get_attribute( pids_id, char_fill,                     &
1207                                       basal_area_density_f%fill,              &
1208                                       .FALSE., 'bad' )
1209!
1210!--                Inquire number of vertical vegetation layer
1211                   CALL get_dimension_length( pids_id,                         &
1212                                              basal_area_density_f%nz,         & 
1213                                              'zlad' )
1214!
1215!--                Allocate variable
1216                   ALLOCATE( basal_area_density_f%var                          &
1217                                              (0:basal_area_density_f%nz-1,    &
1218                                               nys:nyn,nxl:nxr) )
1219
1220                   CALL get_variable( pids_id, 'bad', basal_area_density_f%var,&
1221                                      nxl, nxr, nys, nyn,                      &
1222                                      0,  basal_area_density_f%nz-1 )
1223                ELSE
1224                   basal_area_density_f%from_file = .FALSE.
1225                ENDIF
1226!
1227!--             Read root area density - resolved vegetation
1228                IF ( check_existence( vars_pids, 'root_area_dens_r' ) )  THEN
1229                   root_area_density_lad_f%from_file = .TRUE.
1230                   CALL get_attribute( pids_id, char_fill,                     &
1231                                       root_area_density_lad_f%fill,           &
1232                                       .FALSE., 'root_area_dens_r' )
1233!
1234!--                Inquire number of vertical soil layers
1235                   CALL get_dimension_length( pids_id,                         &
1236                                              root_area_density_lad_f%nz,      &
1237                                              'zsoil' )
1238!
1239!--                Allocate variable
1240                   ALLOCATE( root_area_density_lad_f%var                       &
1241                                               (0:root_area_density_lad_f%nz-1,&
1242                                                nys:nyn,nxl:nxr) )
1243
1244                   CALL get_variable( pids_id, 'root_area_dens_r',             &
1245                                      root_area_density_lad_f%var,             &
1246                                      nxl, nxr, nys, nyn,                      &
1247                                      0,  root_area_density_lad_f%nz-1 )
1248                ELSE
1249                   root_area_density_lad_f%from_file = .FALSE.
1250                ENDIF
1251
1252                DEALLOCATE( vars_pids )
1253!
1254!--             Finally, close the input file and deallocate temporary array
1255                CALL close_input_file( pids_id )
1256#endif
1257             ENDIF
1258
1259!
1260!--          Initialize LAD with data from file. If LAD is given in NetCDF file,
1261!--          use these values, else take LAD profiles from ASCII file.
1262!--          Please note, in NetCDF file LAD is only given up to the maximum
1263!--          canopy top, indicated by leaf_area_density_f%nz. 
1264             lad_s = 0.0_wp
1265             IF ( leaf_area_density_f%from_file )  THEN
1266!
1267!--             Set also pch_index, used to be the upper bound of the vertical
1268!--             loops. Therefore, use the global top of the canopy layer.
1269                pch_index = leaf_area_density_f%nz - 1
1270
1271                DO  i = nxl, nxr
1272                   DO  j = nys, nyn
1273                      DO  k = 0, leaf_area_density_f%nz - 1
1274                         IF ( leaf_area_density_f%var(k,j,i) /=                &
1275                              leaf_area_density_f%fill )                       &
1276                         lad_s(k,j,i) = leaf_area_density_f%var(k,j,i)
1277                      ENDDO
1278!
1279!--                   Check if resolved vegetation is mapped onto buildings.
1280!--                   In general, this is allowed and also meaningful, e.g.
1281!--                   when trees carry across roofs. However, due to the
1282!--                   topography filtering, new building grid points can emerge
1283!--                   at location where also plant canopy is defined. As a
1284!--                   result, plant canopy is mapped on top of roofs, with
1285!--                   siginficant impact on the downstream flow field and the
1286!--                   nearby surface radiation. In order to avoid that
1287!--                   plant canopy is mistakenly mapped onto building roofs,
1288!--                   check for building grid points (bit 6) that emerge from
1289!--                   the filtering (bit 4) and set LAD to zero at these
1290!--                   artificially  created building grid points. This case,
1291!--                   an informative message is given.
1292                      IF ( ANY( lad_s(:,j,i) /= 0.0_wp )  .AND.                &
1293                           ANY( BTEST( wall_flags_total_0(:,j,i), 6 ) ) .AND.  &
1294                           ANY( BTEST( wall_flags_total_0(:,j,i), 4 ) ) )  THEN
1295                         lad_s(:,j,i) = 0.0_wp
1296                         lad_on_top   = .TRUE.
1297                      ENDIF
1298                   ENDDO
1299                ENDDO
1300#if defined( __parallel )
1301               CALL MPI_ALLREDUCE( MPI_IN_PLACE, lad_on_top, 1, MPI_LOGICAL,  &
1302                                   MPI_LOR, comm2d, ierr)
1303#endif
1304                IF ( lad_on_top )  THEN
1305                   WRITE( message_string, * )                                  &
1306                                        'Resolved plant-canopy is ' //         &
1307                                        'defined on top of an artificially '// &
1308                                        'created building grid point(s) ' //   &
1309                                        '(emerged from the filtering) - ' //   &
1310                                        'LAD profile is omitted at this / ' // &
1311                                        'these grid point(s).'
1312                   CALL message( 'pcm_init', 'PA0313', 0, 0, 0, 6, 0 )
1313                ENDIF
1314                CALL exchange_horiz( lad_s, nbgp )
1315!
1316!            ASCII file
1317!--          Initialize canopy parameters canopy_drag_coeff,
1318!--          leaf_scalar_exch_coeff, leaf_surface_conc
1319!--          from file which contains complete 3D data (separate vertical profiles for
1320!--          each location).
1321             ELSE
1322                CALL pcm_read_plant_canopy_3d
1323             ENDIF
1324
1325          CASE DEFAULT
1326!
1327!--          The DEFAULT case is reached either if the parameter
1328!--          canopy mode contains a wrong character string or if the
1329!--          user has coded a special case in the user interface.
1330!--          There, the subroutine user_init_plant_canopy checks
1331!--          which of these two conditions applies.
1332             CALL user_init_plant_canopy
1333 
1334       END SELECT
1335!
1336!--    Check that at least one grid point has an LAD /= 0, else this may
1337!--    cause errors in the radiation model.
1338       lad_max = MAXVAL( lad_s )
1339#if defined( __parallel )
1340       CALL MPI_ALLREDUCE( MPI_IN_PLACE, lad_max, 1, MPI_REAL, MPI_MAX,        &
1341                           comm2d, ierr)
1342#endif
1343       IF ( lad_max <= 0.0_wp )  THEN
1344          message_string = 'Plant-canopy model is switched-on but no ' //      &
1345                           'plant canopy is present in the model domain.'
1346          CALL message( 'pcm_init', 'PA0685', 1, 2, 0, 6, 0 )
1347       ENDIF
1348   
1349!
1350!--    Initialize 2D index array indicating canopy top index.
1351       ALLOCATE( pch_index_ji(nysg:nyng,nxlg:nxrg) )
1352       pch_index_ji = 0
1353       
1354       DO  i = nxlg, nxrg
1355          DO  j = nysg, nyng
1356             DO  k = 0, pch_index
1357                IF ( lad_s(k,j,i) /= 0 )  pch_index_ji(j,i) = k
1358             ENDDO
1359!
1360!--          Check whether topography and local vegetation on top exceed
1361!--          height of the model domain.
1362             IF ( topo_top_ind(j,i,0) + pch_index_ji(j,i) >= nzt + 1 )  THEN
1363                message_string =  'Local vegetation height on top of ' //      &
1364                                  'topography exceeds height of model domain.'
1365                CALL message( 'pcm_init', 'PA0674', 2, 2, myid, 6, 0 )
1366             ENDIF
1367
1368          ENDDO
1369       ENDDO
1370!
1371!--    Calculate global pch_index value (index of top of plant canopy from ground)
1372       pch_index = MAXVAL( pch_index_ji )
1373!
1374!--    Exchange pch_index from all processors
1375#if defined( __parallel )
1376       CALL MPI_ALLREDUCE( MPI_IN_PLACE, pch_index, 1, MPI_INTEGER,            &
1377                           MPI_MAX, comm2d, ierr)
1378#endif
1379!
1380!--    Allocation of arrays pcm_heating_rate, pcm_transpiration_rate and pcm_latent_rate
1381       ALLOCATE( pcm_heating_rate(0:pch_index,nysg:nyng,nxlg:nxrg) )
1382       pcm_heating_rate = 0.0_wp
1383       
1384       IF ( humidity )  THEN
1385          ALLOCATE( pcm_transpiration_rate(0:pch_index,nysg:nyng,nxlg:nxrg) )
1386          pcm_transpiration_rate = 0.0_wp
1387          ALLOCATE( pcm_latent_rate(0:pch_index,nysg:nyng,nxlg:nxrg) )
1388          pcm_latent_rate = 0.0_wp
1389       ENDIF
1390!
1391!--    Initialization of the canopy heat source distribution due to heating
1392!--    of the canopy layers by incoming solar radiation, in case that a non-zero
1393!--    value is set for the canopy top heat flux (cthf), which equals the
1394!--    available net radiation at canopy top.
1395!--    The heat source distribution is calculated by a decaying exponential
1396!--    function of the downward cumulative leaf area index (cum_lai_hf),
1397!--    assuming that the foliage inside the plant canopy is heated by solar
1398!--    radiation penetrating the canopy layers according to the distribution
1399!--    of net radiation as suggested by Brown & Covey (1966; Agric. Meteorol. 3,
1400!--    73–96). This approach has been applied e.g. by Shaw & Schumann (1992;
1401!--    Bound.-Layer Meteorol. 61, 47–64).
1402!--    When using the radiation_interactions, canopy heating (pcm_heating_rate)
1403!--    and plant canopy transpiration (pcm_transpiration_rate, pcm_latent_rate)
1404!--    are calculated in the RTM after the calculation of radiation.
1405       IF ( cthf /= 0.0_wp )  THEN
1406
1407          ALLOCATE( cum_lai_hf(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1408!
1409!--       Piecewise calculation of the cumulative leaf area index by vertical
1410!--       integration of the leaf area density
1411          cum_lai_hf(:,:,:) = 0.0_wp
1412          DO  i = nxlg, nxrg
1413             DO  j = nysg, nyng
1414                DO  k = pch_index_ji(j,i)-1, 0, -1
1415                   IF ( k == pch_index_ji(j,i)-1 )  THEN
1416                      cum_lai_hf(k,j,i) = cum_lai_hf(k+1,j,i) +                &
1417                         ( 0.5_wp * lad_s(k+1,j,i) *                           &
1418                           ( zw(k+1) - zu(k+1) ) )  +                          &
1419                         ( 0.5_wp * ( 0.5_wp * ( lad_s(k+1,j,i) +              &
1420                                                 lad_s(k,j,i) ) +              &
1421                                      lad_s(k+1,j,i) ) *                       &
1422                           ( zu(k+1) - zw(k) ) ) 
1423                   ELSE
1424                      cum_lai_hf(k,j,i) = cum_lai_hf(k+1,j,i) +                &
1425                         ( 0.5_wp * ( 0.5_wp * ( lad_s(k+2,j,i) +              &
1426                                                 lad_s(k+1,j,i) ) +            &
1427                                      lad_s(k+1,j,i) ) *                       &
1428                           ( zw(k+1) - zu(k+1) ) )  +                          &
1429                         ( 0.5_wp * ( 0.5_wp * ( lad_s(k+1,j,i) +              &
1430                                                 lad_s(k,j,i) ) +              &
1431                                      lad_s(k+1,j,i) ) *                       &
1432                           ( zu(k+1) - zw(k) ) )
1433                   ENDIF
1434                ENDDO
1435             ENDDO
1436          ENDDO
1437
1438!
1439!--       In areas with canopy the surface value of the canopy heat
1440!--       flux distribution overrides the surface heat flux (shf)
1441!--       Start with default surface type
1442          DO  m = 1, surf_def_h(0)%ns
1443             i = surf_def_h(0)%i(m)
1444             j = surf_def_h(0)%j(m)
1445             IF ( cum_lai_hf(0,j,i) /= 0.0_wp )                                &
1446                surf_def_h(0)%shf(m) = cthf * exp( -ext_coef * cum_lai_hf(0,j,i) )
1447          ENDDO
1448!
1449!--       Natural surfaces
1450          DO  m = 1, surf_lsm_h(0)%ns
1451             i = surf_lsm_h(0)%i(m)
1452             j = surf_lsm_h(0)%j(m)
1453             IF ( cum_lai_hf(0,j,i) /= 0.0_wp )                                &
1454                surf_lsm_h(0)%shf(m) = cthf * exp( -ext_coef * cum_lai_hf(0,j,i) )
1455          ENDDO
1456!
1457!--       Urban surfaces
1458          DO  m = 1, surf_usm_h(0)%ns
1459             i = surf_usm_h(0)%i(m)
1460             j = surf_usm_h(0)%j(m)
1461             IF ( cum_lai_hf(0,j,i) /= 0.0_wp )                                &
1462                surf_usm_h(0)%shf(m) = cthf * exp( -ext_coef * cum_lai_hf(0,j,i) )
1463          ENDDO
1464!
1465!
1466!--       Calculation of the heating rate (K/s) within the different layers of
1467!--       the plant canopy. Calculation is only necessary in areas covered with
1468!--       canopy.
1469!--       Within the different canopy layers the plant-canopy heating
1470!--       rate (pcm_heating_rate) is calculated as the vertical
1471!--       divergence of the canopy heat fluxes at the top and bottom
1472!--       of the respective layer
1473          DO  i = nxlg, nxrg
1474             DO  j = nysg, nyng
1475                DO  k = 1, pch_index_ji(j,i)
1476                   IF ( cum_lai_hf(0,j,i) /= 0.0_wp )  THEN
1477                      pcm_heating_rate(k,j,i) = cthf *                          &
1478                                ( exp(-ext_coef*cum_lai_hf(k,j,i)) -           &
1479                                  exp(-ext_coef*cum_lai_hf(k-1,j,i) ) ) / dzw(k)
1480                   ENDIF
1481                ENDDO
1482             ENDDO
1483          ENDDO
1484
1485       ENDIF
1486
1487       IF ( debug_output )  CALL debug_message( 'pcm_init', 'end' )
1488
1489    END SUBROUTINE pcm_init
1490
1491
1492!------------------------------------------------------------------------------!
1493! Description:
1494! ------------
1495!> Parin for &plant_canopy_parameters for plant canopy model
1496!------------------------------------------------------------------------------!
1497    SUBROUTINE pcm_parin
1498
1499       CHARACTER (LEN=80) ::  line  !< dummy string that contains the current line of the parameter file
1500       
1501       NAMELIST /plant_canopy_parameters/                                      &
1502                                  alpha_lad, beta_lad, canopy_drag_coeff,      &
1503                                  canopy_mode, cthf,                           &
1504                                  lad_surface, lad_type_coef,                  & 
1505                                  lad_vertical_gradient,                       &
1506                                  lad_vertical_gradient_level,                 &
1507                                  lai_beta,                                    &
1508                                  leaf_scalar_exch_coeff,                      &
1509                                  leaf_surface_conc, pch_index,                &
1510                                  plant_canopy_transpiration
1511
1512       NAMELIST /canopy_par/      alpha_lad, beta_lad, canopy_drag_coeff,      &
1513                                  canopy_mode, cthf,                           &
1514                                  lad_surface, lad_type_coef,                  & 
1515                                  lad_vertical_gradient,                       &
1516                                  lad_vertical_gradient_level,                 &
1517                                  lai_beta,                                    &
1518                                  leaf_scalar_exch_coeff,                      &
1519                                  leaf_surface_conc, pch_index,                &
1520                                  plant_canopy_transpiration
1521
1522       line = ' '
1523
1524!
1525!--    Try to find plant-canopy model package
1526       REWIND ( 11 )
1527       line = ' '
1528       DO WHILE ( INDEX( line, '&plant_canopy_parameters' ) == 0 )
1529          READ ( 11, '(A)', END=12 )  line
1530       ENDDO
1531       BACKSPACE ( 11 )
1532
1533!
1534!--    Read user-defined namelist
1535       READ ( 11, plant_canopy_parameters, ERR = 10 )
1536
1537!
1538!--    Set flag that indicates that the plant-canopy model is switched on
1539       plant_canopy = .TRUE.
1540
1541       GOTO 14
1542
1543 10    BACKSPACE( 11 )
1544       READ( 11 , '(A)') line
1545       CALL parin_fail_message( 'plant_canopy_parameters', line )
1546!
1547!--    Try to find old namelist
1548 12    REWIND ( 11 )
1549       line = ' '
1550       DO WHILE ( INDEX( line, '&canopy_par' ) == 0 )
1551          READ ( 11, '(A)', END=14 )  line
1552       ENDDO
1553       BACKSPACE ( 11 )
1554
1555!
1556!--    Read user-defined namelist
1557       READ ( 11, canopy_par, ERR = 13, END = 14 )
1558
1559       message_string = 'namelist canopy_par is deprecated and will be ' // &
1560                     'removed in near future. Please use namelist ' //      &
1561                     'plant_canopy_parameters instead'
1562       CALL message( 'pcm_parin', 'PA0487', 0, 1, 0, 6, 0 )
1563
1564!
1565!--    Set flag that indicates that the plant-canopy model is switched on
1566       plant_canopy = .TRUE.
1567
1568       GOTO 14
1569
1570 13    BACKSPACE( 11 )
1571       READ( 11 , '(A)') line
1572       CALL parin_fail_message( 'canopy_par', line )
1573
1574 14    CONTINUE
1575
1576    END SUBROUTINE pcm_parin
1577
1578
1579!------------------------------------------------------------------------------!
1580! Description:
1581! ------------
1582!
1583!> Loads 3D plant canopy data from file. File format is as follows:
1584!>
1585!> num_levels
1586!> dtype,x,y,pctype,value(nzb),value(nzb+1), ... ,value(nzb+num_levels-1)
1587!> dtype,x,y,pctype,value(nzb),value(nzb+1), ... ,value(nzb+num_levels-1)
1588!> dtype,x,y,pctype,value(nzb),value(nzb+1), ... ,value(nzb+num_levels-1)
1589!> ...
1590!>
1591!> i.e. first line determines number of levels and further lines represent plant
1592!> canopy data, one line per column and variable. In each data line,
1593!> dtype represents variable to be set:
1594!>
1595!> dtype=1: leaf area density (lad_s)
1596!> dtype=2....n: some additional plant canopy input data quantity
1597!>
1598!> Zeros are added automatically above num_levels until top of domain.  Any
1599!> non-specified (x,y) columns have zero values as default.
1600!------------------------------------------------------------------------------!
1601    SUBROUTINE pcm_read_plant_canopy_3d
1602
1603       USE exchange_horiz_mod,                                                    &
1604           ONLY:  exchange_horiz
1605
1606       INTEGER(iwp)                        ::  dtype     !< type of input data (1=lad)
1607       INTEGER(iwp)                        ::  pctype    !< type of plant canopy (deciduous,non-deciduous,...)
1608       INTEGER(iwp)                        ::  i, j      !< running index
1609       INTEGER(iwp)                        ::  nzp       !< number of vertical layers of plant canopy
1610       INTEGER(iwp)                        ::  nzpltop   !<
1611       INTEGER(iwp)                        ::  nzpl      !<
1612       INTEGER(iwp)                        ::  kk        !<
1613       
1614       REAL(wp), DIMENSION(:), ALLOCATABLE ::  col   !< vertical column of input data
1615
1616!
1617!--    Initialize lad_s array
1618       lad_s = 0.0_wp
1619       
1620!
1621!--    Open and read plant canopy input data
1622       OPEN(152, FILE='PLANT_CANOPY_DATA_3D' // TRIM( coupling_char ),         &
1623                 ACCESS='SEQUENTIAL', ACTION='READ', STATUS='OLD',             &
1624                 FORM='FORMATTED', ERR=515)
1625       READ(152, *, ERR=516, END=517)  nzp   !< read first line = number of vertical layers
1626       nzpltop = MIN(nzt+1, nzb+nzp-1)
1627       nzpl = nzpltop - nzb + 1    !< no. of layers to assign
1628       ALLOCATE( col(0:nzp-1) )
1629
1630       DO
1631          READ(152, *, ERR=516, END=517) dtype, i, j, pctype, col(:)
1632          IF ( i < nxlg  .OR.  i > nxrg  .OR.  j < nysg  .OR.  j > nyng )  CYCLE
1633         
1634          SELECT CASE (dtype)
1635             CASE( 1 )   !< leaf area density
1636!
1637!--             This is just the pure canopy layer assumed to be grounded to
1638!--             a flat domain surface. At locations where plant canopy sits
1639!--             on top of any kind of topography, the vertical plant column
1640!--             must be "lifted", which is done in SUBROUTINE pcm_tendency.           
1641                IF ( pctype < 0  .OR.  pctype > 10 )  THEN   !< incorrect plant canopy type
1642                   WRITE( message_string, * ) 'Incorrect type of plant canopy. '   //  &
1643                                              'Allowed values 0 <= pctype <= 10, ' //  &
1644                                              'but pctype is ', pctype
1645                   CALL message( 'pcm_read_plant_canopy_3d', 'PA0349', 1, 2, 0, 6, 0 )
1646                ENDIF
1647                kk = topo_top_ind(j,i,0)
1648                lad_s(nzb:nzpltop-kk, j, i) = col(kk:nzpl-1)*lad_type_coef(pctype)
1649             CASE DEFAULT
1650                WRITE(message_string, '(a,i2,a)')   &
1651                     'Unknown record type in file PLANT_CANOPY_DATA_3D: "', dtype, '"'
1652                CALL message( 'pcm_read_plant_canopy_3d', 'PA0530', 1, 2, 0, 6, 0 )
1653          END SELECT
1654       ENDDO
1655
1656515    message_string = 'error opening file PLANT_CANOPY_DATA_3D'
1657       CALL message( 'pcm_read_plant_canopy_3d', 'PA0531', 1, 2, 0, 6, 0 )
1658
1659516    message_string = 'error reading file PLANT_CANOPY_DATA_3D'
1660       CALL message( 'pcm_read_plant_canopy_3d', 'PA0532', 1, 2, 0, 6, 0 )
1661
1662517    CLOSE(152)
1663       DEALLOCATE( col )
1664       
1665       CALL exchange_horiz( lad_s, nbgp )
1666       
1667    END SUBROUTINE pcm_read_plant_canopy_3d
1668
1669!------------------------------------------------------------------------------!
1670! Description:
1671! ------------
1672!> Read module-specific global restart data (Fortran binary format).
1673!------------------------------------------------------------------------------!
1674    SUBROUTINE pcm_rrd_global_ftn( found )
1675
1676       LOGICAL, INTENT(OUT)  ::  found
1677
1678       found = .TRUE.
1679
1680       SELECT CASE ( restart_string(1:length) )
1681
1682          CASE ( 'pch_index' )
1683             READ ( 13 )  pch_index
1684
1685          CASE DEFAULT
1686
1687             found = .FALSE.
1688
1689       END SELECT
1690
1691    END SUBROUTINE pcm_rrd_global_ftn
1692
1693!------------------------------------------------------------------------------!
1694! Description:
1695! ------------
1696!> Read module-specific global restart data (MPI-IO).
1697!------------------------------------------------------------------------------!
1698    SUBROUTINE pcm_rrd_global_mpi
1699
1700       CALL rrd_mpi_io( 'pch_index', pch_index )
1701
1702    END SUBROUTINE pcm_rrd_global_mpi
1703
1704
1705!------------------------------------------------------------------------------!
1706! Description:
1707! ------------
1708!> Read module-specific local restart data arrays (Fortran binary format).
1709!------------------------------------------------------------------------------!
1710    SUBROUTINE pcm_rrd_local_ftn( k, nxlf, nxlc, nxl_on_file, nxrf, nxrc,          &
1711                                  nxr_on_file, nynf, nync, nyn_on_file, nysf,      &
1712                                  nysc, nys_on_file, found )
1713
1714       INTEGER(iwp) ::  k               !<
1715       INTEGER(iwp) ::  nxlc            !<
1716       INTEGER(iwp) ::  nxlf            !<
1717       INTEGER(iwp) ::  nxl_on_file     !<
1718       INTEGER(iwp) ::  nxrc            !<
1719       INTEGER(iwp) ::  nxrf            !<
1720       INTEGER(iwp) ::  nxr_on_file     !<
1721       INTEGER(iwp) ::  nync            !<
1722       INTEGER(iwp) ::  nynf            !<
1723       INTEGER(iwp) ::  nyn_on_file     !<
1724       INTEGER(iwp) ::  nysc            !<
1725       INTEGER(iwp) ::  nysf            !<
1726       INTEGER(iwp) ::  nys_on_file     !<
1727
1728       LOGICAL, INTENT(OUT)  :: found
1729
1730       REAL(wp), DIMENSION(0:pch_index,                                        &
1731                           nys_on_file-nbgp:nyn_on_file+nbgp,                  &
1732                           nxl_on_file-nbgp:nxr_on_file+nbgp) :: tmp_3d2  !< temporary 3D array for entire vertical
1733                                                                          !< extension of canopy layer
1734       found = .TRUE.
1735
1736       SELECT CASE ( restart_string(1:length) )
1737
1738          CASE ( 'pcm_heatrate_av' )
1739             IF ( .NOT. ALLOCATED( pcm_heatrate_av ) )  THEN
1740                ALLOCATE( pcm_heatrate_av(0:pch_index,nysg:nyng,nxlg:nxrg) )
1741                pcm_heatrate_av = 0.0_wp
1742             ENDIF 
1743             IF ( k == 1 )  READ ( 13 )  tmp_3d2
1744             pcm_heatrate_av(0:pch_index,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
1745                        tmp_3d2(0:pch_index,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1746
1747          CASE ( 'pcm_latentrate_av' )
1748             IF ( .NOT. ALLOCATED( pcm_latentrate_av ) )  THEN
1749                ALLOCATE( pcm_latentrate_av(0:pch_index,nysg:nyng,nxlg:nxrg) )
1750                pcm_latentrate_av = 0.0_wp
1751             ENDIF 
1752             IF ( k == 1 )  READ ( 13 )  tmp_3d2
1753             pcm_latentrate_av(0:pch_index,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
1754                        tmp_3d2(0:pch_index,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1755
1756          CASE ( 'pcm_transpirationrate_av' )
1757             IF ( .NOT. ALLOCATED( pcm_transpirationrate_av ) )  THEN
1758                ALLOCATE( pcm_transpirationrate_av(0:pch_index,nysg:nyng,nxlg:nxrg) )
1759                pcm_transpirationrate_av = 0.0_wp
1760             ENDIF 
1761             IF ( k == 1 )  READ ( 13 )  tmp_3d2
1762             pcm_transpirationrate_av(0:pch_index,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
1763                        tmp_3d2(0:pch_index,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1764
1765          CASE DEFAULT
1766
1767             found = .FALSE.
1768
1769       END SELECT
1770
1771    END SUBROUTINE pcm_rrd_local_ftn
1772
1773
1774!------------------------------------------------------------------------------!
1775! Description:
1776! ------------
1777!> Read module-specific local restart data arrays (MPI-IO).
1778!------------------------------------------------------------------------------!
1779    SUBROUTINE pcm_rrd_local_mpi
1780
1781       IMPLICIT NONE
1782
1783       LOGICAL ::  array_found  !<
1784
1785       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  tmp_3d  !< temporary array to store pcm data with
1786                                                           !< non-standard vertical index bounds
1787
1788!
1789!--    Plant canopy arrays have non standard reduced vertical index bounds. They are stored with
1790!--    full vertical bounds (bzb:nzt+1) in the restart file and must be re-stored after reading.
1791       CALL rd_mpi_io_check_array( 'pcm_heatrate_av' , found = array_found )
1792       IF ( array_found )  THEN
1793          IF ( .NOT. ALLOCATED( pcm_heatrate_av ) )  THEN
1794             ALLOCATE( pcm_heatrate_av(nzb:pch_index,nysg:nyng,nxlg:nxrg) )
1795          ENDIF
1796          ALLOCATE( tmp_3d(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1797          CALL rrd_mpi_io( 'pcm_heatrate_av', tmp_3d )
1798          pcm_heatrate_av = tmp_3d(nzb:pch_index,:,:)
1799          DEALLOCATE( tmp_3d )
1800       ENDIF
1801
1802       CALL rd_mpi_io_check_array( 'pcm_latentrate_av' , found = array_found )
1803       IF ( array_found )  THEN
1804          IF ( .NOT. ALLOCATED( pcm_latentrate_av ) )  THEN
1805             ALLOCATE( pcm_latentrate_av(nzb:pch_index,nysg:nyng,nxlg:nxrg) )
1806          ENDIF
1807          ALLOCATE( tmp_3d(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1808          CALL rrd_mpi_io( 'pcm_latentrate_av', tmp_3d )
1809          pcm_latentrate_av = tmp_3d(nzb:pch_index,:,:)
1810          DEALLOCATE( tmp_3d )
1811       ENDIF
1812
1813       CALL rd_mpi_io_check_array( 'pcm_transpirationrate_av' , found = array_found )
1814       IF ( array_found )  THEN
1815          IF ( .NOT. ALLOCATED( pcm_transpirationrate_av ) )  THEN
1816             ALLOCATE( pcm_transpirationrate_av(nzb:pch_index,nysg:nyng,nxlg:nxrg) )
1817          ENDIF
1818          ALLOCATE( tmp_3d(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1819          CALL rrd_mpi_io( 'pcm_transpirationrate_av', tmp_3d )
1820          pcm_transpirationrate_av = tmp_3d(nzb:pch_index,:,:)
1821          DEALLOCATE( tmp_3d )
1822       ENDIF
1823
1824    END SUBROUTINE pcm_rrd_local_mpi
1825
1826
1827!------------------------------------------------------------------------------!
1828! Description:
1829! ------------
1830!> Calculation of the tendency terms, accounting for the effect of the plant
1831!> canopy on momentum and scalar quantities.
1832!>
1833!> The canopy is located where the leaf area density lad_s(k,j,i) > 0.0
1834!> (defined on scalar grid), as initialized in subroutine pcm_init.
1835!> The lad on the w-grid is vertically interpolated from the surrounding
1836!> lad_s. The upper boundary of the canopy is defined on the w-grid at
1837!> k = pch_index. Here, the lad is zero.
1838!>
1839!> The canopy drag must be limited (previously accounted for by calculation of
1840!> a limiting canopy timestep for the determination of the maximum LES timestep
1841!> in subroutine timestep), since it is physically impossible that the canopy
1842!> drag alone can locally change the sign of a velocity component. This
1843!> limitation is realized by calculating preliminary tendencies and velocities.
1844!> It is subsequently checked if the preliminary new velocity has a different
1845!> sign than the current velocity. If so, the tendency is limited in a way that
1846!> the velocity can at maximum be reduced to zero by the canopy drag.
1847!>
1848!>
1849!> Call for all grid points
1850!------------------------------------------------------------------------------!
1851    SUBROUTINE pcm_tendency( component )
1852
1853       INTEGER(iwp) ::  component !< prognostic variable (u,v,w,pt,q,e)
1854       INTEGER(iwp) ::  i         !< running index
1855       INTEGER(iwp) ::  j         !< running index
1856       INTEGER(iwp) ::  k         !< running index
1857       INTEGER(iwp) ::  kk        !< running index for flat lad arrays
1858
1859       LOGICAL ::  building_edge_e !< control flag indicating an eastward-facing building edge
1860       LOGICAL ::  building_edge_n !< control flag indicating a north-facing building edge
1861       LOGICAL ::  building_edge_s !< control flag indicating a south-facing building edge
1862       LOGICAL ::  building_edge_w !< control flag indicating a westward-facing building edge
1863
1864       REAL(wp) ::  ddt_3d    !< inverse of the LES timestep (dt_3d)
1865       REAL(wp) ::  lad_local !< local lad value
1866       REAL(wp) ::  pre_tend  !< preliminary tendency
1867       REAL(wp) ::  pre_u     !< preliminary u-value
1868       REAL(wp) ::  pre_v     !< preliminary v-value
1869       REAL(wp) ::  pre_w     !< preliminary w-value
1870
1871
1872       ddt_3d = 1.0_wp / dt_3d
1873 
1874!
1875!--    Compute drag for the three velocity components and the SGS-TKE:
1876       SELECT CASE ( component )
1877
1878!
1879!--       u-component
1880          CASE ( 1 )
1881             DO  i = nxlu, nxr
1882                DO  j = nys, nyn
1883!
1884!--                Set control flags indicating east- and westward-orientated
1885!--                building edges. Note, building_egde_w is set from the perspective
1886!--                of the potential rooftop grid point, while building_edge_e is
1887!--                is set from the perspective of the non-building grid point.
1888                   building_edge_w = ANY( BTEST( wall_flags_total_0(:,j,i),   6 ) )&
1889                        .AND.  .NOT. ANY( BTEST( wall_flags_total_0(:,j,i-1), 6 ) )
1890                   building_edge_e = ANY( BTEST( wall_flags_total_0(:,j,i-1), 6 ) )&
1891                        .AND.  .NOT. ANY( BTEST( wall_flags_total_0(:,j,i),   6 ) )
1892!
1893!--                Determine topography-top index on u-grid
1894                   DO  k = topo_top_ind(j,i,1)+1, topo_top_ind(j,i,1) + pch_index_ji(j,i)
1895
1896                      kk = k - topo_top_ind(j,i,1)   !- lad arrays are defined flat
1897!
1898!--                   In order to create sharp boundaries of the plant canopy,
1899!--                   the lad on the u-grid at index (k,j,i) is equal to lad_s(k,j,i),
1900!--                   rather than being interpolated from the surrounding lad_s,
1901!--                   because this would yield smaller lad at the canopy boundaries
1902!--                   than inside of the canopy.
1903!--                   For the same reason, the lad at the rightmost(i+1)canopy
1904!--                   boundary on the u-grid equals lad_s(k,j,i), which is considered
1905!--                   in the next if-statement. Note, at left-sided building edges
1906!--                   this is not applied, here the LAD is equals the LAD at grid
1907!--                   point (k,j,i), in order to avoid that LAD is mistakenly mapped
1908!--                   on top of a roof where (usually) is no LAD is defined.
1909                      lad_local = lad_s(kk,j,i)
1910                      IF ( lad_local == 0.0_wp .AND. lad_s(kk,j,i-1) > 0.0_wp  &
1911                           .AND.  .NOT. building_edge_w )  lad_local = lad_s(kk,j,i-1)
1912!
1913!--                   In order to avoid that LAD is mistakenly considered at right-
1914!--                   sided building edges (here the topography-top index for the
1915!--                   u-component at index j,i is still on the building while the
1916!--                   topography top for the scalar isn't), LAD is taken from grid
1917!--                   point (j,i-1).
1918                      IF ( lad_local > 0.0_wp .AND. lad_s(kk,j,i-1) == 0.0_wp  &
1919                           .AND.  building_edge_e )  lad_local = lad_s(kk,j,i-1)
1920
1921                      pre_tend = 0.0_wp
1922                      pre_u = 0.0_wp
1923!
1924!--                   Calculate preliminary value (pre_tend) of the tendency
1925                      pre_tend = - canopy_drag_coeff *                         &
1926                                   lad_local *                                 &
1927                                   SQRT( u(k,j,i)**2 +                         &
1928                                         ( 0.25_wp * ( v(k,j,i-1) +            &
1929                                                       v(k,j,i)   +            &
1930                                                       v(k,j+1,i) +            &
1931                                                       v(k,j+1,i-1) )          &
1932                                         )**2 +                                &
1933                                         ( 0.25_wp * ( w(k-1,j,i-1) +          &
1934                                                       w(k-1,j,i)   +          &
1935                                                       w(k,j,i-1)   +          &
1936                                                       w(k,j,i) )              &
1937                                         )**2                                  &
1938                                       ) *                                     &
1939                                   u(k,j,i)
1940
1941!
1942!--                   Calculate preliminary new velocity, based on pre_tend
1943                      pre_u = u(k,j,i) + dt_3d * pre_tend
1944!
1945!--                   Compare sign of old velocity and new preliminary velocity,
1946!--                   and in case the signs are different, limit the tendency
1947                      IF ( SIGN(pre_u,u(k,j,i)) /= pre_u )  THEN
1948                         pre_tend = - u(k,j,i) * ddt_3d
1949                      ENDIF
1950!
1951!--                   Calculate final tendency
1952                      tend(k,j,i) = tend(k,j,i) + pre_tend
1953
1954                   ENDDO
1955                ENDDO
1956             ENDDO
1957
1958!
1959!--       v-component
1960          CASE ( 2 )
1961             DO  i = nxl, nxr
1962                DO  j = nysv, nyn
1963!
1964!--                Set control flags indicating north- and southward-orientated
1965!--                building edges. Note, building_egde_s is set from the perspective
1966!--                of the potential rooftop grid point, while building_edge_n is
1967!--                is set from the perspective of the non-building grid point.
1968                   building_edge_s = ANY( BTEST( wall_flags_total_0(:,j,i),   6 ) )&
1969                        .AND.  .NOT. ANY( BTEST( wall_flags_total_0(:,j-1,i), 6 ) )
1970                   building_edge_n = ANY( BTEST( wall_flags_total_0(:,j-1,i), 6 ) )&
1971                        .AND.  .NOT. ANY( BTEST( wall_flags_total_0(:,j,i),   6 ) )
1972!
1973!--                Determine topography-top index on v-grid
1974                   DO  k = topo_top_ind(j,i,2)+1, topo_top_ind(j,i,2) + pch_index_ji(j,i)
1975
1976                      kk = k - topo_top_ind(j,i,2)   !- lad arrays are defined flat
1977!
1978!--                   In order to create sharp boundaries of the plant canopy,
1979!--                   the lad on the v-grid at index (k,j,i) is equal to lad_s(k,j,i),
1980!--                   rather than being interpolated from the surrounding lad_s,
1981!--                   because this would yield smaller lad at the canopy boundaries
1982!--                   than inside of the canopy.
1983!--                   For the same reason, the lad at the northmost(j+1)canopy
1984!--                   boundary on the v-grid equals lad_s(k,j,i), which is considered
1985!--                   in the next if-statement. Note, at left-sided building edges
1986!--                   this is not applied, here the LAD is equals the LAD at grid
1987!--                   point (k,j,i), in order to avoid that LAD is mistakenly mapped
1988!--                   on top of a roof where (usually) is no LAD is defined.
1989                      lad_local = lad_s(kk,j,i)
1990                      IF ( lad_local == 0.0_wp .AND. lad_s(kk,j-1,i) > 0.0_wp &
1991                       .AND.  .NOT. building_edge_s )  lad_local = lad_s(kk,j-1,i)
1992!
1993!--                   In order to avoid that LAD is mistakenly considered at right-
1994!--                   sided building edges (here the topography-top index for the
1995!--                   u-component at index j,i is still on the building while the
1996!--                   topography top for the scalar isn't), LAD is taken from grid
1997!--                   point (j,i-1).
1998                      IF ( lad_local > 0.0_wp .AND. lad_s(kk,j-1,i) == 0.0_wp  &
1999                       .AND.  building_edge_n )  lad_local = lad_s(kk,j-1,i)
2000
2001                      pre_tend = 0.0_wp
2002                      pre_v = 0.0_wp
2003!
2004!--                   Calculate preliminary value (pre_tend) of the tendency
2005                      pre_tend = - canopy_drag_coeff *                         &
2006                                   lad_local *                                 &
2007                                   SQRT( ( 0.25_wp * ( u(k,j-1,i)   +          &
2008                                                       u(k,j-1,i+1) +          &
2009                                                       u(k,j,i)     +          &
2010                                                       u(k,j,i+1) )            &
2011                                         )**2 +                                &
2012                                         v(k,j,i)**2 +                         &
2013                                         ( 0.25_wp * ( w(k-1,j-1,i) +          &
2014                                                       w(k-1,j,i)   +          &
2015                                                       w(k,j-1,i)   +          &
2016                                                       w(k,j,i) )              &
2017                                         )**2                                  &
2018                                       ) *                                     &
2019                                   v(k,j,i)
2020
2021!
2022!--                   Calculate preliminary new velocity, based on pre_tend
2023                      pre_v = v(k,j,i) + dt_3d * pre_tend
2024!
2025!--                   Compare sign of old velocity and new preliminary velocity,
2026!--                   and in case the signs are different, limit the tendency
2027                      IF ( SIGN(pre_v,v(k,j,i)) /= pre_v )  THEN
2028                         pre_tend = - v(k,j,i) * ddt_3d
2029                      ELSE
2030                         pre_tend = pre_tend
2031                      ENDIF
2032!
2033!--                   Calculate final tendency
2034                      tend(k,j,i) = tend(k,j,i) + pre_tend
2035
2036                   ENDDO
2037                ENDDO
2038             ENDDO
2039
2040!
2041!--       w-component
2042          CASE ( 3 )
2043             DO  i = nxl, nxr
2044                DO  j = nys, nyn
2045!
2046!--                Determine topography-top index on w-grid
2047                   DO  k = topo_top_ind(j,i,3)+1, topo_top_ind(j,i,3) + pch_index_ji(j,i) - 1
2048
2049                      kk = k - topo_top_ind(j,i,3)   !- lad arrays are defined flat
2050
2051                      pre_tend = 0.0_wp
2052                      pre_w = 0.0_wp
2053!
2054!--                   Calculate preliminary value (pre_tend) of the tendency
2055                      pre_tend = - canopy_drag_coeff *                         &
2056                                   (0.5_wp *                                   &
2057                                      ( lad_s(kk+1,j,i) + lad_s(kk,j,i) )) *   &
2058                                   SQRT( ( 0.25_wp * ( u(k,j,i)   +            &
2059                                                       u(k,j,i+1) +            &
2060                                                       u(k+1,j,i) +            &
2061                                                       u(k+1,j,i+1) )          &
2062                                         )**2 +                                &
2063                                         ( 0.25_wp * ( v(k,j,i)   +            &
2064                                                       v(k,j+1,i) +            &
2065                                                       v(k+1,j,i) +            &
2066                                                       v(k+1,j+1,i) )          &
2067                                         )**2 +                                &
2068                                         w(k,j,i)**2                           &
2069                                       ) *                                     &
2070                                   w(k,j,i)
2071!
2072!--                   Calculate preliminary new velocity, based on pre_tend
2073                      pre_w = w(k,j,i) + dt_3d * pre_tend
2074!
2075!--                   Compare sign of old velocity and new preliminary velocity,
2076!--                   and in case the signs are different, limit the tendency
2077                      IF ( SIGN(pre_w,w(k,j,i)) /= pre_w )  THEN
2078                         pre_tend = - w(k,j,i) * ddt_3d
2079                      ELSE
2080                         pre_tend = pre_tend
2081                      ENDIF
2082!
2083!--                   Calculate final tendency
2084                      tend(k,j,i) = tend(k,j,i) + pre_tend
2085
2086                   ENDDO
2087                ENDDO
2088             ENDDO
2089
2090!
2091!--       potential temperature
2092          CASE ( 4 )
2093             IF ( humidity ) THEN
2094                DO  i = nxl, nxr
2095                   DO  j = nys, nyn
2096!--                   Determine topography-top index on scalar-grid
2097                      DO  k = topo_top_ind(j,i,0)+1, topo_top_ind(j,i,0) + pch_index_ji(j,i)
2098                         kk = k - topo_top_ind(j,i,0)   !- lad arrays are defined flat
2099                         tend(k,j,i) = tend(k,j,i) + pcm_heating_rate(kk,j,i) - pcm_latent_rate(kk,j,i)
2100                      ENDDO
2101                   ENDDO
2102                ENDDO
2103             ELSE
2104                DO  i = nxl, nxr
2105                   DO  j = nys, nyn
2106!--                   Determine topography-top index on scalar-grid
2107                      DO  k = topo_top_ind(j,i,0)+1, topo_top_ind(j,i,0) + pch_index_ji(j,i)
2108                         kk = k - topo_top_ind(j,i,0)   !- lad arrays are defined flat
2109                         tend(k,j,i) = tend(k,j,i) + pcm_heating_rate(kk,j,i)
2110                      ENDDO
2111                   ENDDO
2112                ENDDO
2113             ENDIF
2114
2115!
2116!--       humidity
2117          CASE ( 5 )
2118             DO  i = nxl, nxr
2119                DO  j = nys, nyn
2120!
2121!--                Determine topography-top index on scalar-grid
2122                   DO  k = topo_top_ind(j,i,0)+1, topo_top_ind(j,i,0) + pch_index_ji(j,i)
2123
2124                      kk = k - topo_top_ind(j,i,0)   !- lad arrays are defined flat
2125
2126                      IF ( .NOT. plant_canopy_transpiration ) THEN
2127                         ! pcm_transpiration_rate is calculated in radiation model
2128                         ! in case of plant_canopy_transpiration = .T.
2129                         ! to include also the dependecy to the radiation
2130                         ! in the plant canopy box
2131                         pcm_transpiration_rate(kk,j,i) =  - leaf_scalar_exch_coeff &
2132                                          * lad_s(kk,j,i) *                         &
2133                                          SQRT( ( 0.5_wp * ( u(k,j,i) +             &
2134                                                             u(k,j,i+1) )           &
2135                                                )**2 +                              &
2136                                                ( 0.5_wp * ( v(k,j,i) +             &
2137                                                             v(k,j+1,i) )           &
2138                                                )**2 +                              &
2139                                                ( 0.5_wp * ( w(k-1,j,i) +           &
2140                                                             w(k,j,i) )             &
2141                                                )**2                                &
2142                                              ) *                                   &
2143                                          ( q(k,j,i) - leaf_surface_conc )
2144                      ENDIF
2145
2146                      tend(k,j,i) = tend(k,j,i) + pcm_transpiration_rate(kk,j,i)
2147                   ENDDO
2148                ENDDO
2149             ENDDO
2150
2151!
2152!--       sgs-tke
2153          CASE ( 6 )
2154             DO  i = nxl, nxr
2155                DO  j = nys, nyn
2156!
2157!--                Determine topography-top index on scalar-grid
2158                   DO  k = topo_top_ind(j,i,0)+1, topo_top_ind(j,i,0) + pch_index_ji(j,i)
2159
2160                      kk = k - topo_top_ind(j,i,0)   !- lad arrays are defined flat
2161                      tend(k,j,i) = tend(k,j,i) -                              &
2162                                       2.0_wp * canopy_drag_coeff *            &
2163                                       lad_s(kk,j,i) *                         &
2164                                       SQRT( ( 0.5_wp * ( u(k,j,i) +           &
2165                                                          u(k,j,i+1) )         &
2166                                             )**2 +                            &
2167                                             ( 0.5_wp * ( v(k,j,i) +           &
2168                                                          v(k,j+1,i) )         &
2169                                             )**2 +                            &
2170                                             ( 0.5_wp * ( w(k,j,i) +           &
2171                                                          w(k+1,j,i) )         &
2172                                             )**2                              &
2173                                           ) *                                 &
2174                                       e(k,j,i)
2175                   ENDDO
2176                ENDDO
2177             ENDDO 
2178!
2179!--       scalar concentration
2180          CASE ( 7 )
2181             DO  i = nxl, nxr
2182                DO  j = nys, nyn
2183!
2184!--                Determine topography-top index on scalar-grid
2185                   DO  k = topo_top_ind(j,i,0)+1, topo_top_ind(j,i,0) + pch_index_ji(j,i)
2186
2187                      kk = k - topo_top_ind(j,i,0)   !- lad arrays are defined flat
2188                      tend(k,j,i) = tend(k,j,i) -                              &
2189                                       leaf_scalar_exch_coeff *                &
2190                                       lad_s(kk,j,i) *                         &
2191                                       SQRT( ( 0.5_wp * ( u(k,j,i) +           &
2192                                                          u(k,j,i+1) )         &
2193                                             )**2 +                            &
2194                                             ( 0.5_wp * ( v(k,j,i) +           &
2195                                                          v(k,j+1,i) )         &
2196                                             )**2 +                            &
2197                                             ( 0.5_wp * ( w(k-1,j,i) +         & 
2198                                                          w(k,j,i) )           &
2199                                             )**2                              &
2200                                           ) *                                 &
2201                                       ( s(k,j,i) - leaf_surface_conc )
2202                   ENDDO
2203                ENDDO
2204             ENDDO   
2205
2206
2207
2208          CASE DEFAULT
2209
2210             WRITE( message_string, * ) 'wrong component: ', component
2211             CALL message( 'pcm_tendency', 'PA0279', 1, 2, 0, 6, 0 ) 
2212
2213       END SELECT
2214
2215    END SUBROUTINE pcm_tendency
2216
2217
2218!------------------------------------------------------------------------------!
2219! Description:
2220! ------------
2221!> Calculation of the tendency terms, accounting for the effect of the plant
2222!> canopy on momentum and scalar quantities.
2223!>
2224!> The canopy is located where the leaf area density lad_s(k,j,i) > 0.0
2225!> (defined on scalar grid), as initialized in subroutine pcm_init.
2226!> The lad on the w-grid is vertically interpolated from the surrounding
2227!> lad_s. The upper boundary of the canopy is defined on the w-grid at
2228!> k = pch_index. Here, the lad is zero.
2229!>
2230!> The canopy drag must be limited (previously accounted for by calculation of
2231!> a limiting canopy timestep for the determination of the maximum LES timestep
2232!> in subroutine timestep), since it is physically impossible that the canopy
2233!> drag alone can locally change the sign of a velocity component. This
2234!> limitation is realized by calculating preliminary tendencies and velocities.
2235!> It is subsequently checked if the preliminary new velocity has a different
2236!> sign than the current velocity. If so, the tendency is limited in a way that
2237!> the velocity can at maximum be reduced to zero by the canopy drag.
2238!>
2239!>
2240!> Call for grid point i,j
2241!------------------------------------------------------------------------------!
2242    SUBROUTINE pcm_tendency_ij( i, j, component )
2243
2244       INTEGER(iwp) ::  component !< prognostic variable (u,v,w,pt,q,e)
2245       INTEGER(iwp) ::  i         !< running index
2246       INTEGER(iwp) ::  j         !< running index
2247       INTEGER(iwp) ::  k         !< running index
2248       INTEGER(iwp) ::  kk        !< running index for flat lad arrays
2249
2250       LOGICAL ::  building_edge_e !< control flag indicating an eastward-facing building edge
2251       LOGICAL ::  building_edge_n !< control flag indicating a north-facing building edge
2252       LOGICAL ::  building_edge_s !< control flag indicating a south-facing building edge
2253       LOGICAL ::  building_edge_w !< control flag indicating a westward-facing building edge
2254
2255       REAL(wp) ::  ddt_3d    !< inverse of the LES timestep (dt_3d)
2256       REAL(wp) ::  lad_local !< local lad value
2257       REAL(wp) ::  pre_tend  !< preliminary tendency
2258       REAL(wp) ::  pre_u     !< preliminary u-value
2259       REAL(wp) ::  pre_v     !< preliminary v-value
2260       REAL(wp) ::  pre_w     !< preliminary w-value
2261
2262
2263       ddt_3d = 1.0_wp / dt_3d
2264!
2265!--    Compute drag for the three velocity components and the SGS-TKE
2266       SELECT CASE ( component )
2267
2268!
2269!--       u-component
2270          CASE ( 1 )
2271!
2272!--          Set control flags indicating east- and westward-orientated
2273!--          building edges. Note, building_egde_w is set from the perspective
2274!--          of the potential rooftop grid point, while building_edge_e is
2275!--          is set from the perspective of the non-building grid point.
2276             building_edge_w = ANY( BTEST( wall_flags_total_0(:,j,i),   6 ) )  .AND. &
2277                         .NOT. ANY( BTEST( wall_flags_total_0(:,j,i-1), 6 ) )
2278             building_edge_e = ANY( BTEST( wall_flags_total_0(:,j,i-1), 6 ) )  .AND. &
2279                         .NOT. ANY( BTEST( wall_flags_total_0(:,j,i),   6 ) )
2280!
2281!--          Determine topography-top index on u-grid
2282             DO  k = topo_top_ind(j,i,1) + 1, topo_top_ind(j,i,1) + pch_index_ji(j,i)
2283
2284                kk = k - topo_top_ind(j,i,1)  !- lad arrays are defined flat
2285
2286!
2287!--             In order to create sharp boundaries of the plant canopy,
2288!--             the lad on the u-grid at index (k,j,i) is equal to lad_s(k,j,i),
2289!--             rather than being interpolated from the surrounding lad_s,
2290!--             because this would yield smaller lad at the canopy boundaries
2291!--             than inside of the canopy.
2292!--             For the same reason, the lad at the rightmost(i+1)canopy
2293!--             boundary on the u-grid equals lad_s(k,j,i), which is considered
2294!--             in the next if-statement. Note, at left-sided building edges
2295!--             this is not applied, here the LAD is equals the LAD at grid
2296!--             point (k,j,i), in order to avoid that LAD is mistakenly mapped
2297!--             on top of a roof where (usually) is no LAD is defined.
2298                lad_local = lad_s(kk,j,i)
2299                IF ( lad_local == 0.0_wp .AND. lad_s(kk,j,i-1) > 0.0_wp  .AND. &
2300                     .NOT. building_edge_w )  lad_local = lad_s(kk,j,i-1)
2301!
2302!--             In order to avoid that LAD is mistakenly considered at right-
2303!--             sided building edges (here the topography-top index for the
2304!--             u-component at index j,i is still on the building while the
2305!--             topography top for the scalar isn't), LAD is taken from grid
2306!--             point (j,i-1).
2307                IF ( lad_local > 0.0_wp .AND. lad_s(kk,j,i-1) == 0.0_wp  .AND. &
2308                     building_edge_e )  lad_local = lad_s(kk,j,i-1)
2309
2310                pre_tend = 0.0_wp
2311                pre_u = 0.0_wp
2312!
2313!--             Calculate preliminary value (pre_tend) of the tendency
2314                pre_tend = - canopy_drag_coeff *                               &
2315                             lad_local *                                       &   
2316                             SQRT( u(k,j,i)**2 +                               &
2317                                   ( 0.25_wp * ( v(k,j,i-1)  +                 &
2318                                                 v(k,j,i)    +                 &
2319                                                 v(k,j+1,i)  +                 &
2320                                                 v(k,j+1,i-1) )                &
2321                                   )**2 +                                      &
2322                                   ( 0.25_wp * ( w(k-1,j,i-1) +                &
2323                                                 w(k-1,j,i)   +                &
2324                                                 w(k,j,i-1)   +                &
2325                                                 w(k,j,i) )                    &
2326                                   )**2                                        &
2327                                 ) *                                           &
2328                             u(k,j,i)
2329
2330!
2331!--             Calculate preliminary new velocity, based on pre_tend
2332                pre_u = u(k,j,i) + dt_3d * pre_tend
2333!
2334!--             Compare sign of old velocity and new preliminary velocity,
2335!--             and in case the signs are different, limit the tendency
2336                IF ( SIGN(pre_u,u(k,j,i)) /= pre_u )  THEN
2337                   pre_tend = - u(k,j,i) * ddt_3d
2338                ELSE
2339                   pre_tend = pre_tend
2340                ENDIF
2341!
2342!--             Calculate final tendency
2343                tend(k,j,i) = tend(k,j,i) + pre_tend
2344             ENDDO
2345
2346
2347!
2348!--       v-component
2349          CASE ( 2 )
2350!
2351!--          Set control flags indicating north- and southward-orientated
2352!--          building edges. Note, building_egde_s is set from the perspective
2353!--          of the potential rooftop grid point, while building_edge_n is
2354!--          is set from the perspective of the non-building grid point.
2355             building_edge_s = ANY( BTEST( wall_flags_total_0(:,j,i),   6 ) )  .AND. &
2356                         .NOT. ANY( BTEST( wall_flags_total_0(:,j-1,i), 6 ) )
2357             building_edge_n = ANY( BTEST( wall_flags_total_0(:,j-1,i), 6 ) )  .AND. &
2358                         .NOT. ANY( BTEST( wall_flags_total_0(:,j,i),   6 ) )
2359!
2360!--          Determine topography-top index on v-grid
2361             DO  k = topo_top_ind(j,i,2) + 1, topo_top_ind(j,i,2) + pch_index_ji(j,i)
2362
2363                kk = k - topo_top_ind(j,i,2)  !- lad arrays are defined flat
2364!
2365!--             In order to create sharp boundaries of the plant canopy,
2366!--             the lad on the v-grid at index (k,j,i) is equal to lad_s(k,j,i),
2367!--             rather than being interpolated from the surrounding lad_s,
2368!--             because this would yield smaller lad at the canopy boundaries
2369!--             than inside of the canopy.
2370!--             For the same reason, the lad at the northmost(j+1)canopy
2371!--             boundary on the v-grid equals lad_s(k,j,i), which is considered
2372!--             in the next if-statement. Note, at left-sided building edges
2373!--             this is not applied, here the LAD is equals the LAD at grid
2374!--             point (k,j,i), in order to avoid that LAD is mistakenly mapped
2375!--             on top of a roof where (usually) is no LAD is defined.
2376                lad_local = lad_s(kk,j,i)
2377                IF ( lad_local == 0.0_wp .AND. lad_s(kk,j-1,i) > 0.0_wp  .AND. &
2378                     .NOT. building_edge_s )  lad_local = lad_s(kk,j-1,i)
2379!
2380!--             In order to avoid that LAD is mistakenly considered at right-
2381!--             sided building edges (here the topography-top index for the
2382!--             u-component at index j,i is still on the building while the
2383!--             topography top for the scalar isn't), LAD is taken from grid
2384!--             point (j,i-1).
2385                IF ( lad_local > 0.0_wp .AND. lad_s(kk,j-1,i) == 0.0_wp  .AND. &
2386                     building_edge_n )  lad_local = lad_s(kk,j-1,i)
2387
2388                pre_tend = 0.0_wp
2389                pre_v = 0.0_wp
2390!
2391!--             Calculate preliminary value (pre_tend) of the tendency
2392                pre_tend = - canopy_drag_coeff *                               &
2393                             lad_local *                                       &
2394                             SQRT( ( 0.25_wp * ( u(k,j-1,i)   +                &
2395                                                 u(k,j-1,i+1) +                &
2396                                                 u(k,j,i)     +                &
2397                                                 u(k,j,i+1) )                  &
2398                                   )**2 +                                      &
2399                                   v(k,j,i)**2 +                               &
2400                                   ( 0.25_wp * ( w(k-1,j-1,i) +                &
2401                                                 w(k-1,j,i)   +                &
2402                                                 w(k,j-1,i)   +                &
2403                                                 w(k,j,i) )                    &
2404                                   )**2                                        &
2405                                 ) *                                           &
2406                             v(k,j,i)
2407
2408!
2409!--             Calculate preliminary new velocity, based on pre_tend
2410                pre_v = v(k,j,i) + dt_3d * pre_tend
2411!
2412!--             Compare sign of old velocity and new preliminary velocity,
2413!--             and in case the signs are different, limit the tendency
2414                IF ( SIGN(pre_v,v(k,j,i)) /= pre_v )  THEN
2415                   pre_tend = - v(k,j,i) * ddt_3d
2416                ELSE
2417                   pre_tend = pre_tend
2418                ENDIF
2419!
2420!--             Calculate final tendency
2421                tend(k,j,i) = tend(k,j,i) + pre_tend
2422             ENDDO
2423
2424
2425!
2426!--       w-component
2427          CASE ( 3 )
2428!
2429!--          Determine topography-top index on w-grid
2430             DO  k = topo_top_ind(j,i,3) + 1, topo_top_ind(j,i,3) + pch_index_ji(j,i) - 1
2431
2432                kk = k - topo_top_ind(j,i,3)  !- lad arrays are defined flat
2433
2434                pre_tend = 0.0_wp
2435                pre_w = 0.0_wp
2436!
2437!--             Calculate preliminary value (pre_tend) of the tendency
2438                pre_tend = - canopy_drag_coeff *                               &
2439                             (0.5_wp *                                         &
2440                                ( lad_s(kk+1,j,i) + lad_s(kk,j,i) )) *         &
2441                             SQRT( ( 0.25_wp * ( u(k,j,i)    +                 & 
2442                                                 u(k,j,i+1)  +                 &
2443                                                 u(k+1,j,i)  +                 &
2444                                                 u(k+1,j,i+1) )                &
2445                                   )**2 +                                      &
2446                                   ( 0.25_wp * ( v(k,j,i)    +                 &
2447                                                 v(k,j+1,i)  +                 &
2448                                                 v(k+1,j,i)  +                 &
2449                                                 v(k+1,j+1,i) )                &
2450                                   )**2 +                                      &
2451                                   w(k,j,i)**2                                 &
2452                                 ) *                                           &
2453                             w(k,j,i)
2454!
2455!--             Calculate preliminary new velocity, based on pre_tend
2456                pre_w = w(k,j,i) + dt_3d * pre_tend
2457!
2458!--             Compare sign of old velocity and new preliminary velocity,
2459!--             and in case the signs are different, limit the tendency
2460                IF ( SIGN(pre_w,w(k,j,i)) /= pre_w )  THEN
2461                   pre_tend = - w(k,j,i) * ddt_3d
2462                ELSE
2463                   pre_tend = pre_tend
2464                ENDIF
2465!
2466!--             Calculate final tendency
2467                tend(k,j,i) = tend(k,j,i) + pre_tend
2468             ENDDO
2469
2470!
2471!--       potential temperature
2472          CASE ( 4 )
2473!
2474!--          Determine topography-top index on scalar grid
2475             IF ( humidity ) THEN
2476                DO  k = topo_top_ind(j,i,0) + 1, topo_top_ind(j,i,0) + pch_index_ji(j,i)
2477                   kk = k - topo_top_ind(j,i,0)  !- lad arrays are defined flat
2478                   tend(k,j,i) = tend(k,j,i) + pcm_heating_rate(kk,j,i) -       &
2479                                 pcm_latent_rate(kk,j,i)
2480                ENDDO
2481             ELSE
2482                DO  k = topo_top_ind(j,i,0) + 1, topo_top_ind(j,i,0) + pch_index_ji(j,i)
2483                   kk = k - topo_top_ind(j,i,0)  !- lad arrays are defined flat
2484                   tend(k,j,i) = tend(k,j,i) + pcm_heating_rate(kk,j,i)
2485                ENDDO
2486             ENDIF
2487
2488!
2489!--       humidity
2490          CASE ( 5 )
2491!
2492!--          Determine topography-top index on scalar grid
2493             DO  k = topo_top_ind(j,i,0) + 1, topo_top_ind(j,i,0) + pch_index_ji(j,i)
2494                kk = k - topo_top_ind(j,i,0)  !- lad arrays are defined flat
2495                IF ( .NOT. plant_canopy_transpiration ) THEN
2496                   ! pcm_transpiration_rate is calculated in radiation model
2497                   ! in case of plant_canopy_transpiration = .T.
2498                   ! to include also the dependecy to the radiation
2499                   ! in the plant canopy box
2500                   pcm_transpiration_rate(kk,j,i) = - leaf_scalar_exch_coeff   &
2501                                    * lad_s(kk,j,i) *                          &
2502                                    SQRT( ( 0.5_wp * ( u(k,j,i) +              &
2503                                                       u(k,j,i+1) )            &
2504                                          )**2  +                              &
2505                                          ( 0.5_wp * ( v(k,j,i) +              &
2506                                                       v(k,j+1,i) )            &
2507                                          )**2 +                               &
2508                                          ( 0.5_wp * ( w(k-1,j,i) +            &
2509                                                       w(k,j,i) )              &
2510                                          )**2                                 &
2511                                        ) *                                    &
2512                                    ( q(k,j,i) - leaf_surface_conc )
2513                ENDIF
2514
2515                tend(k,j,i) = tend(k,j,i) + pcm_transpiration_rate(kk,j,i)
2516
2517             ENDDO   
2518
2519!
2520!--       sgs-tke
2521          CASE ( 6 )
2522!
2523!--          Determine topography-top index on scalar grid
2524             DO  k = topo_top_ind(j,i,0) + 1, topo_top_ind(j,i,0) + pch_index_ji(j,i)
2525
2526                kk = k - topo_top_ind(j,i,0)
2527                tend(k,j,i) = tend(k,j,i) -                                    &
2528                                 2.0_wp * canopy_drag_coeff *                  &
2529                                 lad_s(kk,j,i) *                               &
2530                                 SQRT( ( 0.5_wp * ( u(k,j,i) +                 &
2531                                                    u(k,j,i+1) )               &
2532                                       )**2 +                                  & 
2533                                       ( 0.5_wp * ( v(k,j,i) +                 &
2534                                                    v(k,j+1,i) )               &
2535                                       )**2 +                                  &
2536                                       ( 0.5_wp * ( w(k,j,i) +                 &
2537                                                    w(k+1,j,i) )               &
2538                                       )**2                                    &
2539                                     ) *                                       &
2540                                 e(k,j,i)
2541             ENDDO
2542             
2543!
2544!--       scalar concentration
2545          CASE ( 7 )
2546!
2547!--          Determine topography-top index on scalar grid
2548             DO  k = topo_top_ind(j,i,0) + 1, topo_top_ind(j,i,0) + pch_index_ji(j,i)
2549
2550                kk = k - topo_top_ind(j,i,0)
2551                tend(k,j,i) = tend(k,j,i) -                                    &
2552                                 leaf_scalar_exch_coeff *                      &
2553                                 lad_s(kk,j,i) *                               &
2554                                 SQRT( ( 0.5_wp * ( u(k,j,i) +                 &
2555                                                    u(k,j,i+1) )               &
2556                                       )**2  +                                 &
2557                                       ( 0.5_wp * ( v(k,j,i) +                 &
2558                                                    v(k,j+1,i) )               &
2559                                       )**2 +                                  &
2560                                       ( 0.5_wp * ( w(k-1,j,i) +               &
2561                                                    w(k,j,i) )                 &
2562                                       )**2                                    &
2563                                     ) *                                       &
2564                                 ( s(k,j,i) - leaf_surface_conc )
2565             ENDDO               
2566
2567       CASE DEFAULT
2568
2569          WRITE( message_string, * ) 'wrong component: ', component
2570          CALL message( 'pcm_tendency', 'PA0279', 1, 2, 0, 6, 0 ) 
2571
2572       END SELECT
2573
2574    END SUBROUTINE pcm_tendency_ij
2575
2576!------------------------------------------------------------------------------!
2577! Description:
2578! ------------
2579!> Subroutine writes global restart data
2580!------------------------------------------------------------------------------!
2581    SUBROUTINE pcm_wrd_global
2582
2583       IF ( TRIM( restart_data_format_output ) == 'fortran_binary' )  THEN
2584
2585          CALL wrd_write_string( 'pch_index' )
2586          WRITE ( 14 )  pch_index
2587
2588       ELSEIF ( restart_data_format_output(1:3) == 'mpi' )  THEN
2589
2590          CALL wrd_mpi_io( 'pch_index', pch_index )
2591
2592       ENDIF
2593
2594    END SUBROUTINE pcm_wrd_global
2595
2596!------------------------------------------------------------------------------!
2597! Description:
2598! ------------
2599!> Subroutine writes local (subdomain) restart data
2600!------------------------------------------------------------------------------!
2601    SUBROUTINE pcm_wrd_local
2602
2603       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  tmp_3d  !< temporary array to store pcm data with
2604                                                           !< non-standard vertical index bounds
2605
2606       IF ( TRIM( restart_data_format_output ) == 'fortran_binary' )  THEN
2607
2608          IF ( ALLOCATED( pcm_heatrate_av ) )  THEN
2609             CALL wrd_write_string( 'pcm_heatrate_av' )
2610             WRITE ( 14 )  pcm_heatrate_av
2611          ENDIF
2612
2613          IF ( ALLOCATED( pcm_latentrate_av ) )  THEN
2614             CALL wrd_write_string( 'pcm_latentrate_av' )
2615             WRITE ( 14 )  pcm_latentrate_av
2616          ENDIF
2617
2618          IF ( ALLOCATED( pcm_transpirationrate_av ) )  THEN
2619             CALL wrd_write_string( 'pcm_transpirationrate_av' )
2620             WRITE ( 14 )  pcm_transpirationrate_av
2621          ENDIF
2622
2623       ELSEIF ( restart_data_format_output(1:3) == 'mpi' )  THEN
2624
2625!
2626!--       Plant canopy arrays have non standard reduced vertical index bounds. They are stored with
2627!--       full vertical bounds (bzb:nzt+1) in the restart file and must be re-stored before writing.
2628          IF ( ALLOCATED( pcm_heatrate_av ) )  THEN
2629             ALLOCATE( tmp_3d(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2630             tmp_3d(nzb:pch_index,:,:)     = pcm_heatrate_av
2631             tmp_3d(pch_index+1:nzt+1,:,:) = 0.0_wp
2632             CALL wrd_mpi_io( 'pcm_heatrate_av', tmp_3d )
2633             DEALLOCATE( tmp_3d )
2634          ENDIF
2635          IF ( ALLOCATED( pcm_latentrate_av ) )  THEN
2636             ALLOCATE( tmp_3d(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2637             tmp_3d(nzb:pch_index,:,:)     = pcm_latentrate_av
2638             tmp_3d(pch_index+1:nzt+1,:,:) = 0.0_wp
2639             CALL wrd_mpi_io( 'pcm_latentrate_av', tmp_3d )
2640             DEALLOCATE( tmp_3d )
2641          ENDIF
2642          IF ( ALLOCATED( pcm_transpirationrate_av ) )  THEN
2643             ALLOCATE( tmp_3d(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2644             tmp_3d(nzb:pch_index,:,:)     = pcm_transpirationrate_av
2645             tmp_3d(pch_index+1:nzt+1,:,:) = 0.0_wp
2646             CALL wrd_mpi_io( 'pcm_transpirationrate_av', tmp_3d )
2647             DEALLOCATE( tmp_3d )
2648          ENDIF
2649
2650       ENDIF
2651
2652    END SUBROUTINE pcm_wrd_local
2653
2654
2655 END MODULE plant_canopy_model_mod
Note: See TracBrowser for help on using the repository browser.