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

Last change on this file since 3241 was 3241, checked in by raasch, 6 years ago

various changes to avoid compiler warnings (mainly removal of unused variables)

  • Property svn:keywords set to Id
File size: 75.3 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-2018 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! ------------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: plant_canopy_model_mod.f90 3241 2018-09-12 15:02:00Z raasch $
27! unused variables removed
28!
29! 3065 2018-06-12 07:03:02Z Giersch
30! dz was replaced by the help of zw to allow for vertical stretching
31!
32! 3049 2018-05-29 13:52:36Z Giersch
33! Error messages revised
34!
35! 3045 2018-05-28 07:55:41Z Giersch
36! Error message revised
37!
38! 3022 2018-05-18 11:12:35Z suehring
39! Bugfix in allocation of transpiration rate
40!
41! 3014 2018-05-09 08:42:38Z maronga
42! Bugfix: nzb_do and nzt_do were not used for 3d data output
43! Added pc_transpiration_rate
44!
45! 2977 2018-04-17 10:27:57Z kanani
46! Implement changes from branch radiation (r2948-2971) with minor modifications,
47! plus some formatting.
48! (moh.hefny):
49! Add plant canopy type to account for changes in LAD (based on the changes
50! done by Resler & Pavel) and correct the error message to PALM Standard.
51!
52! 2932 2018-03-26 09:39:22Z maronga
53! renamed canopy_par to plant_canopy_parameters
54!
55! 2920 2018-03-22 11:22:01Z kanani
56! Move usm_lad_rma and prototype_lad to radiation_model (moh.hefny)
57!
58! 2892 2018-03-14 15:06:29Z suehring
59! Bugfix, read separate ASCII LAD files for parent and child model.
60!
61! 2770 2018-01-25 15:10:09Z kanani
62! Correction of parameter check
63!
64! 2768 2018-01-24 15:38:29Z kanani
65! Added check for output quantity pcm_heatrate, some formatting
66!
67! 2766 2018-01-22 17:17:47Z kanani
68! Increased LEN of canopy mode to 30
69!
70! 2746 2018-01-15 12:06:04Z suehring
71! Move flag plant canopy to modules
72!
73! 2718 2018-01-02 08:49:38Z maronga
74! Corrected "Former revisions" section
75!
76! 2701 2017-12-15 15:40:50Z suehring
77! Changes from last commit documented
78!
79! 2698 2017-12-14 18:46:24Z suehring
80! Bugfix in get_topography_top_index
81!
82! 2696 2017-12-14 17:12:51Z kanani
83! Change in file header (GPL part)
84! Bugfix for vertical loop index pch_index in case of Netcdf input
85! Introduce 2D index array incorporate canopy top index
86! Check if canopy on top of topography do not exceed vertical dimension
87! Add check for canopy_mode in case of Netcdf input.
88! Enable _FillValue output for 3d quantities
89! Bugfix in reading of PIDS leaf area density (MS)
90!
91! 2669 2017-12-06 16:03:27Z raasch
92! coupling_char removed
93!
94! 2512 2017-10-04 08:26:59Z raasch
95! upper bounds of 3d output changed from nx+1,ny+1 to nx,ny
96! no output of ghost layer data
97!
98! 2318 2017-07-20 17:27:44Z suehring
99! Get topography top index via Function call
100!
101! 2317 2017-07-20 17:27:19Z suehring
102! Changed error messages
103!
104! 2233 2017-05-30 18:08:54Z suehring
105!
106! 2232 2017-05-30 17:47:52Z suehring
107! Adjustments to new topography concept
108!
109! 2213 2017-04-24 15:10:35Z kanani
110! Bugfix: exchange of ghost points in array pc_heating_rate needed for output
111! of pcm_heatrate, onetime ghost point exchange of lad_s after initialization.
112! Formatting and clean-up of subroutine pcm_read_plant_canopy_3d,
113! minor re-organization of canopy-heating initialization.
114!
115! 2209 2017-04-19 09:34:46Z kanani
116! Added 3d output of leaf area density (pcm_lad) and canopy
117! heat rate (pcm_heatrate)
118!
119! 2024 2016-10-12 16:42:37Z kanani
120! Added missing lad_s initialization
121!
122! 2011 2016-09-19 17:29:57Z kanani
123! Renamed canopy_heat_flux to pc_heating_rate, since the original meaning/
124! calculation of the quantity has changed, related to the urban surface model
125! and similar future applications.
126!
127! 2007 2016-08-24 15:47:17Z kanani
128! Added SUBROUTINE pcm_read_plant_canopy_3d for reading 3d plant canopy data
129! from file (new case canopy_mode=read_from_file_3d) in the course of
130! introduction of urban surface model,
131! introduced variable ext_coef,
132! resorted SUBROUTINEs to alphabetical order
133!
134! 2000 2016-08-20 18:09:15Z knoop
135! Forced header and separation lines into 80 columns
136!
137! 1960 2016-07-12 16:34:24Z suehring
138! Separate humidity and passive scalar
139!
140! 1953 2016-06-21 09:28:42Z suehring
141! Bugfix, lad_s and lad must be public
142!
143! 1826 2016-04-07 12:01:39Z maronga
144! Further modularization
145!
146! 1721 2015-11-16 12:56:48Z raasch
147! bugfixes: shf is reduced in areas covered with canopy only,
148!           canopy is set on top of topography
149!
150! 1682 2015-10-07 23:56:08Z knoop
151! Code annotations made doxygen readable
152!
153! 1484 2014-10-21 10:53:05Z kanani
154! Changes due to new module structure of the plant canopy model:
155!   module plant_canopy_model_mod now contains a subroutine for the
156!   initialization of the canopy model (pcm_init),
157!   limitation of the canopy drag (previously accounted for by calculation of
158!   a limiting canopy timestep for the determination of the maximum LES timestep
159!   in subroutine timestep) is now realized by the calculation of pre-tendencies
160!   and preliminary velocities in subroutine pcm_tendency,
161!   some redundant MPI communication removed in subroutine pcm_init
162!   (was previously in init_3d_model),
163!   unnecessary 3d-arrays lad_u, lad_v, lad_w removed - lad information on the
164!   respective grid is now provided only by lad_s (e.g. in the calculation of
165!   the tendency terms or of cum_lai_hf),
166!   drag_coefficient, lai, leaf_surface_concentration,
167!   scalar_exchange_coefficient, sec and sls renamed to canopy_drag_coeff,
168!   cum_lai_hf, leaf_surface_conc, leaf_scalar_exch_coeff, lsec and lsc,
169!   respectively,
170!   unnecessary 3d-arrays cdc, lsc and lsec now defined as single-value constants,
171!   USE-statements and ONLY-lists modified accordingly
172!
173! 1340 2014-03-25 19:45:13Z kanani
174! REAL constants defined as wp-kind
175!
176! 1320 2014-03-20 08:40:49Z raasch
177! ONLY-attribute added to USE-statements,
178! kind-parameters added to all INTEGER and REAL declaration statements,
179! kinds are defined in new module kinds,
180! old module precision_kind is removed,
181! revision history before 2012 removed,
182! comment fields (!:) to be used for variable explanations added to
183! all variable declaration statements
184!
185! 1036 2012-10-22 13:43:42Z raasch
186! code put under GPL (PALM 3.9)
187!
188! 138 2007-11-28 10:03:58Z letzel
189! Initial revision
190!
191! Description:
192! ------------
193!> 1) Initialization of the canopy model, e.g. construction of leaf area density
194!> profile (subroutine pcm_init).
195!> 2) Calculation of sinks and sources of momentum, heat and scalar concentration
196!> due to canopy elements (subroutine pcm_tendency).
197!------------------------------------------------------------------------------!
198 MODULE plant_canopy_model_mod
199 
200    USE arrays_3d,                                                             &
201        ONLY:  dzu, dzw, e, q, s, tend, u, v, w, zu, zw 
202
203    USE indices,                                                               &
204        ONLY:  nbgp, nxl, nxlg, nxlu, nxr, nxrg, nyn, nyng, nys, nysg, nysv,   &
205               nz, nzb, nzt
206
207    USE kinds
208
209    USE surface_mod,                                                           &
210        ONLY:  get_topography_top_index_ji
211
212
213    IMPLICIT NONE
214
215
216    CHARACTER (LEN=30)   ::  canopy_mode = 'block' !< canopy coverage
217
218    INTEGER(iwp) ::  pch_index = 0                               !< plant canopy height/top index
219    INTEGER(iwp) ::  lad_vertical_gradient_level_ind(10) = -9999 !< lad-profile levels (index)
220
221    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  pch_index_ji   !< local plant canopy top
222
223    LOGICAL ::  calc_beta_lad_profile = .FALSE. !< switch for calc. of lad from beta func.
224
225    REAL(wp) ::  alpha_lad = 9999999.9_wp         !< coefficient for lad calculation
226    REAL(wp) ::  beta_lad = 9999999.9_wp          !< coefficient for lad calculation
227    REAL(wp) ::  canopy_drag_coeff = 0.0_wp       !< canopy drag coefficient (parameter)
228    REAL(wp) ::  cdc = 0.0_wp                     !< canopy drag coeff. (abbreviation used in equations)
229    REAL(wp) ::  cthf = 0.0_wp                    !< canopy top heat flux
230    REAL(wp) ::  dt_plant_canopy = 0.0_wp         !< timestep account. for canopy drag
231    REAL(wp) ::  ext_coef = 0.6_wp                !< extinction coefficient
232    REAL(wp) ::  lad_surface = 0.0_wp             !< lad surface value
233    REAL(wp) ::  lai_beta = 0.0_wp                !< leaf area index (lai) for lad calc.
234    REAL(wp) ::  leaf_scalar_exch_coeff = 0.0_wp  !< canopy scalar exchange coeff.
235    REAL(wp) ::  leaf_surface_conc = 0.0_wp       !< leaf surface concentration
236    REAL(wp) ::  lsc = 0.0_wp                     !< leaf surface concentration
237    REAL(wp) ::  lsec = 0.0_wp                    !< leaf scalar exchange coeff.
238
239    REAL(wp) ::  lad_vertical_gradient(10) = 0.0_wp              !< lad gradient
240    REAL(wp) ::  lad_vertical_gradient_level(10) = -9999999.9_wp !< lad-prof. levels (in m)
241
242    REAL(wp) ::  lad_type_coef(0:10) = 1.0_wp   !< multiplicative coeficients for particular types
243                                                !< of plant canopy (e.g. deciduous tree during winter)
244
245    REAL(wp), DIMENSION(:), ALLOCATABLE ::  lad            !< leaf area density
246    REAL(wp), DIMENSION(:), ALLOCATABLE ::  pre_lad        !< preliminary lad
247   
248    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  cum_lai_hf       !< cumulative lai for heatflux calc.
249    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  lad_s            !< lad on scalar-grid
250    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pc_heating_rate  !< plant canopy heating rate
251    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pc_transpiration_rate  !< plant canopy transpiration rate
252
253    SAVE
254
255
256    PRIVATE
257 
258!
259!-- Public functions
260    PUBLIC pcm_check_data_output, pcm_check_parameters, pcm_data_output_3d,    &
261           pcm_define_netcdf_grid, pcm_header, pcm_init, pcm_parin, pcm_tendency
262
263!
264!-- Public variables and constants
265    PUBLIC pc_heating_rate, pc_transpiration_rate, canopy_mode, cthf, dt_plant_canopy, lad, lad_s,   &
266           pch_index
267           
268
269    INTERFACE pcm_check_data_output
270       MODULE PROCEDURE pcm_check_data_output
271    END INTERFACE pcm_check_data_output
272   
273    INTERFACE pcm_check_parameters
274       MODULE PROCEDURE pcm_check_parameters
275    END INTERFACE pcm_check_parameters
276
277    INTERFACE pcm_data_output_3d
278       MODULE PROCEDURE pcm_data_output_3d
279    END INTERFACE pcm_data_output_3d
280
281    INTERFACE pcm_define_netcdf_grid
282       MODULE PROCEDURE pcm_define_netcdf_grid
283    END INTERFACE pcm_define_netcdf_grid
284   
285     INTERFACE pcm_header
286       MODULE PROCEDURE pcm_header
287    END INTERFACE pcm_header       
288   
289    INTERFACE pcm_init
290       MODULE PROCEDURE pcm_init
291    END INTERFACE pcm_init
292
293    INTERFACE pcm_parin
294       MODULE PROCEDURE pcm_parin
295    END INTERFACE pcm_parin
296
297    INTERFACE pcm_read_plant_canopy_3d
298       MODULE PROCEDURE pcm_read_plant_canopy_3d
299    END INTERFACE pcm_read_plant_canopy_3d
300   
301    INTERFACE pcm_tendency
302       MODULE PROCEDURE pcm_tendency
303       MODULE PROCEDURE pcm_tendency_ij
304    END INTERFACE pcm_tendency
305
306
307 CONTAINS
308
309
310!------------------------------------------------------------------------------!
311! Description:
312! ------------
313!> Check data output for plant canopy model
314!------------------------------------------------------------------------------!
315 SUBROUTINE pcm_check_data_output( var, unit )
316 
317 
318    USE control_parameters,                                                 &
319        ONLY:  message_string, urban_surface
320
321    IMPLICIT NONE
322
323    CHARACTER (LEN=*) ::  unit  !<
324    CHARACTER (LEN=*) ::  var   !<
325
326
327    SELECT CASE ( TRIM( var ) )
328
329       CASE ( 'pcm_heatrate' )
330          IF ( cthf == 0.0_wp  .AND. .NOT.  urban_surface )  THEN
331             message_string = 'output of "' // TRIM( var ) // '" requi' //  &
332                              'res setting of parameter cthf /= 0.0'
333             CALL message( 'pcm_check_data_output', 'PA1000', 1, 2, 0, 6, 0 )
334          ENDIF
335          unit = 'K s-1'
336   
337       CASE ( 'pcm_transpirationrate' )
338          unit = 'kg kg-1 s-1'
339
340       CASE ( 'pcm_lad' )
341          unit = 'm2 m-3'
342
343
344       CASE DEFAULT
345          unit = 'illegal'
346
347    END SELECT
348
349
350 END SUBROUTINE pcm_check_data_output
351 
352 
353!------------------------------------------------------------------------------!
354! Description:
355! ------------
356!> Check parameters routine for plant canopy model
357!------------------------------------------------------------------------------!
358    SUBROUTINE pcm_check_parameters
359
360       USE control_parameters,                                                 &
361           ONLY: cloud_physics, coupling_char, message_string,                 &
362                 microphysics_seifert
363
364       USE netcdf_data_input_mod,                                              &
365           ONLY:  input_file_static, input_pids_static
366                 
367   
368       IMPLICIT NONE
369
370   
371       IF ( canopy_drag_coeff == 0.0_wp )  THEN
372          message_string = 'plant_canopy = .TRUE. requires a non-zero drag '// &
373                           'coefficient & given value is canopy_drag_coeff = 0.0'
374          CALL message( 'pcm_check_parameters', 'PA0041', 1, 2, 0, 6, 0 )
375       ENDIF
376   
377       IF ( ( alpha_lad /= 9999999.9_wp  .AND.  beta_lad == 9999999.9_wp ) .OR.&
378              beta_lad /= 9999999.9_wp   .AND.  alpha_lad == 9999999.9_wp )  THEN
379          message_string = 'using the beta function for the construction ' //  &
380                           'of the leaf area density profile requires '    //  &
381                           'both alpha_lad and beta_lad to be /= 9999999.9'
382          CALL message( 'pcm_check_parameters', 'PA0118', 1, 2, 0, 6, 0 )
383       ENDIF
384   
385       IF ( calc_beta_lad_profile  .AND.  lai_beta == 0.0_wp )  THEN
386          message_string = 'using the beta function for the construction ' //  &
387                           'of the leaf area density profile requires '    //  &
388                           'a non-zero lai_beta, but given value is '      //  &
389                           'lai_beta = 0.0'
390          CALL message( 'pcm_check_parameters', 'PA0119', 1, 2, 0, 6, 0 )
391       ENDIF
392
393       IF ( calc_beta_lad_profile  .AND.  lad_surface /= 0.0_wp )  THEN
394          message_string = 'simultaneous setting of alpha_lad /= 9999999.9 '// &
395                           'combined with beta_lad /= 9999999.9 '           // &
396                           'and lad_surface /= 0.0 is not possible, '       // &
397                           'use either vertical gradients or the beta '     // &
398                           'function for the construction of the leaf area '// &
399                           'density profile'
400          CALL message( 'pcm_check_parameters', 'PA0120', 1, 2, 0, 6, 0 )
401       ENDIF
402
403       IF ( cloud_physics  .AND.  microphysics_seifert )  THEN
404          message_string = 'plant_canopy = .TRUE. requires cloud_scheme /=' // &
405                          ' seifert_beheng'
406          CALL message( 'pcm_check_parameters', 'PA0360', 1, 2, 0, 6, 0 )
407       ENDIF
408!
409!--    If dynamic input file is used, canopy need to be read from file
410       IF ( input_pids_static  .AND.                                           &
411            TRIM( canopy_mode ) /= 'read_from_file_3d' )  THEN
412          message_string = 'Usage of dynamic input file ' //                   &
413                           TRIM( input_file_static ) //                        &
414                           TRIM( coupling_char ) // ' requires ' //            &
415                           'canopy_mode = read_from_file_3d'
416          CALL message( 'pcm_check_parameters', 'PA0999', 1, 2, 0, 6, 0 )
417       ENDIF
418
419 
420    END SUBROUTINE pcm_check_parameters 
421 
422
423!------------------------------------------------------------------------------!
424!
425! Description:
426! ------------
427!> Subroutine defining 3D output variables
428!------------------------------------------------------------------------------!
429 SUBROUTINE pcm_data_output_3d( av, variable, found, local_pf, fill_value,     &
430                                nzb_do, nzt_do )
431 
432    USE indices
433
434    USE kinds
435
436
437    IMPLICIT NONE
438
439    CHARACTER (LEN=*) ::  variable !<
440
441    INTEGER(iwp) ::  av     !<
442    INTEGER(iwp) ::  i      !<
443    INTEGER(iwp) ::  j      !<
444    INTEGER(iwp) ::  k      !<
445    INTEGER(iwp) ::  k_topo !< topography top index
446    INTEGER(iwp) ::  nzb_do !< lower limit of the data output (usually 0)
447    INTEGER(iwp) ::  nzt_do !< vertical upper limit of the data output (usually nz_do3d)
448
449    LOGICAL      ::  found !<
450
451    REAL(wp)     ::  fill_value
452    REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !<
453
454
455    found = .TRUE.
456
457    local_pf = REAL( fill_value, KIND = 4 )
458
459    SELECT CASE ( TRIM( variable ) )
460
461      CASE ( 'pcm_heatrate' )
462         IF ( av == 0 )  THEN
463            DO  i = nxl, nxr
464               DO  j = nys, nyn
465                  IF ( pch_index_ji(j,i) /= 0 )  THEN
466                     k_topo = get_topography_top_index_ji( j, i, 's' )
467                     DO  k = k_topo, k_topo + pch_index_ji(j,i)
468                        local_pf(i,j,k) = pc_heating_rate(k-k_topo,j,i)
469                     ENDDO
470                  ENDIF
471               ENDDO
472            ENDDO
473         ENDIF
474   
475       CASE ( 'pcm_transpirationrate' )
476         IF ( av == 0 )  THEN
477            DO  i = nxl, nxr
478               DO  j = nys, nyn
479                  IF ( pch_index_ji(j,i) /= 0 )  THEN
480                     k_topo = get_topography_top_index_ji( j, i, 's' )
481                     DO  k = k_topo, k_topo + pch_index_ji(j,i)
482                        local_pf(i,j,k) = pc_transpiration_rate(k-k_topo,j,i)
483                     ENDDO
484                  ENDIF
485               ENDDO
486            ENDDO
487         ENDIF
488   
489      CASE ( 'pcm_lad' )
490         IF ( av == 0 )  THEN
491            DO  i = nxl, nxr
492               DO  j = nys, nyn
493                  IF ( pch_index_ji(j,i) /= 0 )  THEN
494                     k_topo = get_topography_top_index_ji( j, i, 's' )
495                     DO  k = k_topo, k_topo + pch_index_ji(j,i)
496                        local_pf(i,j,k) = lad_s(k-k_topo,j,i)
497                     ENDDO
498                  ENDIF
499               ENDDO
500            ENDDO
501         ENDIF
502                 
503         
504       CASE DEFAULT
505          found = .FALSE.
506
507    END SELECT
508
509
510 END SUBROUTINE pcm_data_output_3d 
511         
512!------------------------------------------------------------------------------!
513!
514! Description:
515! ------------
516!> Subroutine defining appropriate grid for netcdf variables.
517!> It is called from subroutine netcdf.
518!------------------------------------------------------------------------------!
519 SUBROUTINE pcm_define_netcdf_grid( var, found, grid_x, grid_y, grid_z )
520   
521     IMPLICIT NONE
522
523     CHARACTER (LEN=*), INTENT(IN)  ::  var         !<
524     LOGICAL, INTENT(OUT)           ::  found       !<
525     CHARACTER (LEN=*), INTENT(OUT) ::  grid_x      !<
526     CHARACTER (LEN=*), INTENT(OUT) ::  grid_y      !<
527     CHARACTER (LEN=*), INTENT(OUT) ::  grid_z      !<
528
529     found  = .TRUE.
530
531!
532!--  Check for the grid
533     SELECT CASE ( TRIM( var ) )
534
535        CASE ( 'pcm_heatrate', 'pcm_lad', 'pcm_transpirationrate')
536           grid_x = 'x'
537           grid_y = 'y'
538           grid_z = 'zu'
539
540        CASE DEFAULT
541           found  = .FALSE.
542           grid_x = 'none'
543           grid_y = 'none'
544           grid_z = 'none'
545     END SELECT
546
547 END SUBROUTINE pcm_define_netcdf_grid
548 
549 
550!------------------------------------------------------------------------------!
551! Description:
552! ------------
553!> Header output for plant canopy model
554!------------------------------------------------------------------------------!
555    SUBROUTINE pcm_header ( io )
556
557       USE control_parameters,                                                 &
558           ONLY: passive_scalar
559
560
561       IMPLICIT NONE
562 
563       CHARACTER (LEN=10) ::  coor_chr            !<
564
565       CHARACTER (LEN=86) ::  coordinates         !<
566       CHARACTER (LEN=86) ::  gradients           !<
567       CHARACTER (LEN=86) ::  leaf_area_density   !<
568       CHARACTER (LEN=86) ::  slices              !<
569 
570       INTEGER(iwp) :: i                !<
571       INTEGER(iwp),  INTENT(IN) ::  io !< Unit of the output file
572       INTEGER(iwp) :: k                !<       
573   
574       REAL(wp) ::  canopy_height       !< canopy height (in m)
575       
576       canopy_height = zw(pch_index)
577
578       WRITE ( io, 1 )  canopy_mode, canopy_height, pch_index,                 &
579                          canopy_drag_coeff
580       IF ( passive_scalar )  THEN
581          WRITE ( io, 2 )  leaf_scalar_exch_coeff,                             &
582                             leaf_surface_conc
583       ENDIF
584
585!
586!--    Heat flux at the top of vegetation
587       WRITE ( io, 3 )  cthf
588
589!
590!--    Leaf area density profile, calculated either from given vertical
591!--    gradients or from beta probability density function.
592       IF (  .NOT.  calc_beta_lad_profile )  THEN
593
594!--       Building output strings, starting with surface value
595          WRITE ( leaf_area_density, '(F7.4)' )  lad_surface
596          gradients = '------'
597          slices = '     0'
598          coordinates = '   0.0'
599          i = 1
600          DO  WHILE ( i < 11  .AND.  lad_vertical_gradient_level_ind(i)        &
601                      /= -9999 )
602
603             WRITE (coor_chr,'(F7.2)')  lad(lad_vertical_gradient_level_ind(i))
604             leaf_area_density = TRIM( leaf_area_density ) // ' ' //           &
605                                 TRIM( coor_chr )
606 
607             WRITE (coor_chr,'(F7.2)')  lad_vertical_gradient(i)
608             gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
609
610             WRITE (coor_chr,'(I7)')  lad_vertical_gradient_level_ind(i)
611             slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
612
613             WRITE (coor_chr,'(F7.1)')  lad_vertical_gradient_level(i)
614             coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
615
616             i = i + 1
617          ENDDO
618
619          WRITE ( io, 4 )  TRIM( coordinates ), TRIM( leaf_area_density ),     &
620                             TRIM( gradients ), TRIM( slices )
621
622       ELSE
623       
624          WRITE ( leaf_area_density, '(F7.4)' )  lad_surface
625          coordinates = '   0.0'
626         
627          DO  k = 1, pch_index
628
629             WRITE (coor_chr,'(F7.2)')  lad(k)
630             leaf_area_density = TRIM( leaf_area_density ) // ' ' //           &
631                                 TRIM( coor_chr )
632 
633             WRITE (coor_chr,'(F7.1)')  zu(k)
634             coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
635
636          ENDDO       
637
638          WRITE ( io, 5 ) TRIM( coordinates ), TRIM( leaf_area_density ),      &
639                          alpha_lad, beta_lad, lai_beta
640
641       ENDIF 
642
6431 FORMAT (//' Vegetation canopy (drag) model:'/                                &
644              ' ------------------------------'//                              &
645              ' Canopy mode: ', A /                                            &
646              ' Canopy height: ',F6.2,'m (',I4,' grid points)' /               &
647              ' Leaf drag coefficient: ',F6.2 /)
6482 FORMAT (/ ' Scalar exchange coefficient: ',F6.2 /                            &
649              ' Scalar concentration at leaf surfaces in kg/m**3: ',F6.2 /)
6503 FORMAT (' Predefined constant heatflux at the top of the vegetation: ',F6.2, &
651          ' K m/s')
6524 FORMAT (/ ' Characteristic levels of the leaf area density:'//               &
653              ' Height:              ',A,'  m'/                                &
654              ' Leaf area density:   ',A,'  m**2/m**3'/                        &
655              ' Gradient:            ',A,'  m**2/m**4'/                        &
656              ' Gridpoint:           ',A)
6575 FORMAT (//' Characteristic levels of the leaf area density and coefficients:'&
658          //  ' Height:              ',A,'  m'/                                &
659              ' Leaf area density:   ',A,'  m**2/m**3'/                        &
660              ' Coefficient alpha: ',F6.2 /                                    &
661              ' Coefficient beta: ',F6.2 /                                     &
662              ' Leaf area index: ',F6.2,'  m**2/m**2' /)   
663       
664    END SUBROUTINE pcm_header
665 
666 
667!------------------------------------------------------------------------------!
668! Description:
669! ------------
670!> Initialization of the plant canopy model
671!------------------------------------------------------------------------------!
672    SUBROUTINE pcm_init
673   
674
675       USE control_parameters,                                                 &
676           ONLY: humidity, message_string, ocean, urban_surface
677
678       USE netcdf_data_input_mod,                                              &
679           ONLY:  leaf_area_density_f
680
681       USE surface_mod,                                                        &
682           ONLY: surf_def_h, surf_lsm_h, surf_usm_h
683
684       IMPLICIT NONE
685
686       INTEGER(iwp) ::  i   !< running index
687       INTEGER(iwp) ::  j   !< running index
688       INTEGER(iwp) ::  k   !< running index
689       INTEGER(iwp) ::  m   !< running index
690
691       REAL(wp) ::  int_bpdf        !< vertical integral for lad-profile construction
692       REAL(wp) ::  gradient        !< gradient for lad-profile construction
693       REAL(wp) ::  canopy_height   !< canopy height for lad-profile construction
694
695!
696!--    Allocate one-dimensional arrays for the computation of the
697!--    leaf area density (lad) profile
698       ALLOCATE( lad(0:nz+1), pre_lad(0:nz+1) )
699       lad = 0.0_wp
700       pre_lad = 0.0_wp
701
702!
703!--    Set flag that indicates that the lad-profile shall be calculated by using
704!--    a beta probability density function
705       IF ( alpha_lad /= 9999999.9_wp  .AND.  beta_lad /= 9999999.9_wp )  THEN
706          calc_beta_lad_profile = .TRUE.
707       ENDIF
708       
709       
710!
711!--    Compute the profile of leaf area density used in the plant
712!--    canopy model. The profile can either be constructed from
713!--    prescribed vertical gradients of the leaf area density or by
714!--    using a beta probability density function (see e.g. Markkanen et al.,
715!--    2003: Boundary-Layer Meteorology, 106, 437-459)
716       IF (  .NOT.  calc_beta_lad_profile )  THEN   
717
718!
719!--       Use vertical gradients for lad-profile construction   
720          i = 1
721          gradient = 0.0_wp
722
723          IF (  .NOT.  ocean )  THEN
724
725             lad(0) = lad_surface
726             lad_vertical_gradient_level_ind(1) = 0
727 
728             DO k = 1, pch_index
729                IF ( i < 11 )  THEN
730                   IF ( lad_vertical_gradient_level(i) < zu(k)  .AND.          &
731                        lad_vertical_gradient_level(i) >= 0.0_wp )  THEN
732                      gradient = lad_vertical_gradient(i)
733                      lad_vertical_gradient_level_ind(i) = k - 1
734                      i = i + 1
735                   ENDIF
736                ENDIF
737                IF ( gradient /= 0.0_wp )  THEN
738                   IF ( k /= 1 )  THEN
739                      lad(k) = lad(k-1) + dzu(k) * gradient
740                   ELSE
741                      lad(k) = lad_surface + dzu(k) * gradient
742                   ENDIF
743                ELSE
744                   lad(k) = lad(k-1)
745                ENDIF
746             ENDDO
747
748          ENDIF
749
750!
751!--       In case of no given leaf area density gradients, choose a vanishing
752!--       gradient. This information is used for the HEADER and the RUN_CONTROL
753!--       file.
754          IF ( lad_vertical_gradient_level(1) == -9999999.9_wp )  THEN
755             lad_vertical_gradient_level(1) = 0.0_wp
756          ENDIF
757
758       ELSE
759
760!
761!--       Use beta function for lad-profile construction
762          int_bpdf = 0.0_wp
763          canopy_height = zw(pch_index)
764
765          DO k = 0, pch_index
766             int_bpdf = int_bpdf +                                             &
767                      ( ( ( zw(k) / canopy_height )**( alpha_lad-1.0_wp ) ) *  &
768                      ( ( 1.0_wp - ( zw(k) / canopy_height ) )**(              &
769                          beta_lad-1.0_wp ) )                                  &
770                      * ( ( zw(k+1)-zw(k) ) / canopy_height ) )
771          ENDDO
772
773!
774!--       Preliminary lad profile (defined on w-grid)
775          DO k = 0, pch_index
776             pre_lad(k) =  lai_beta *                                          &
777                        ( ( ( zw(k) / canopy_height )**( alpha_lad-1.0_wp ) )  &
778                        * ( ( 1.0_wp - ( zw(k) / canopy_height ) )**(          &
779                              beta_lad-1.0_wp ) ) / int_bpdf                   &
780                        ) / canopy_height
781          ENDDO
782
783!
784!--       Final lad profile (defined on scalar-grid level, since most prognostic
785!--       quantities are defined there, hence, less interpolation is required
786!--       when calculating the canopy tendencies)
787          lad(0) = pre_lad(0)
788          DO k = 1, pch_index
789             lad(k) = 0.5 * ( pre_lad(k-1) + pre_lad(k) )
790          ENDDO         
791
792       ENDIF
793
794!
795!--    Allocate 3D-array for the leaf area density (lad_s).
796       ALLOCATE( lad_s(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
797
798!
799!--    Initialize canopy parameters cdc (canopy drag coefficient),
800!--    lsec (leaf scalar exchange coefficient), lsc (leaf surface concentration)
801!--    with the prescribed values
802       cdc = canopy_drag_coeff
803       lsec = leaf_scalar_exch_coeff
804       lsc = leaf_surface_conc
805
806!
807!--    Initialization of the canopy coverage in the model domain:
808!--    Setting the parameter canopy_mode = 'block' initializes a canopy, which
809!--    fully covers the domain surface
810       SELECT CASE ( TRIM( canopy_mode ) )
811
812          CASE( 'block' )
813
814             DO  i = nxlg, nxrg
815                DO  j = nysg, nyng
816                   lad_s(:,j,i) = lad(:)
817                ENDDO
818             ENDDO
819
820          CASE ( 'read_from_file_3d' )
821!
822!--          Initialize LAD with data from file. If LAD is given in NetCDF file,
823!--          use these values, else take LAD profiles from ASCII file.
824!--          Please note, in NetCDF file LAD is only given up to the maximum
825!--          canopy top, indicated by leaf_area_density_f%nz. 
826             lad_s = 0.0_wp
827             IF ( leaf_area_density_f%from_file )  THEN
828!
829!--             Set also pch_index, used to be the upper bound of the vertical
830!--             loops. Therefore, use the global top of the canopy layer.
831                pch_index = leaf_area_density_f%nz - 1
832
833                DO  i = nxl, nxr
834                   DO  j = nys, nyn
835                      DO  k = 0, leaf_area_density_f%nz - 1
836                      IF ( leaf_area_density_f%var(k,j,i) /=                   &
837                           leaf_area_density_f%fill )                          &
838                         lad_s(k,j,i) = leaf_area_density_f%var(k,j,i)
839                      ENDDO
840                   ENDDO
841                ENDDO
842                CALL exchange_horiz( lad_s, nbgp )
843!
844!            ASCII file
845!--          Initialize canopy parameters cdc (canopy drag coefficient),
846!--          lsec (leaf scalar exchange coefficient), lsc (leaf surface concentration)
847!--          from file which contains complete 3D data (separate vertical profiles for
848!--          each location).
849             ELSE
850                CALL pcm_read_plant_canopy_3d
851             ENDIF
852
853          CASE DEFAULT
854!
855!--          The DEFAULT case is reached either if the parameter
856!--          canopy mode contains a wrong character string or if the
857!--          user has coded a special case in the user interface.
858!--          There, the subroutine user_init_plant_canopy checks
859!--          which of these two conditions applies.
860             CALL user_init_plant_canopy
861 
862       END SELECT
863!
864!--    Initialize 2D index array indicating canopy top index.
865       ALLOCATE( pch_index_ji(nysg:nyng,nxlg:nxrg) )
866       pch_index_ji = 0
867
868       DO  i = nxl, nxr
869          DO  j = nys, nyn
870             DO  k = 0, pch_index
871                IF ( lad_s(k,j,i) /= 0 )  pch_index_ji(j,i) = k
872             ENDDO
873!
874!--          Check whether topography and local vegetation on top exceed
875!--          height of the model domain.
876             k = get_topography_top_index_ji( j, i, 's' )
877             IF ( k + pch_index_ji(j,i) >= nzt + 1 )  THEN
878                message_string =  'Local vegetation height on top of ' //      &
879                                  'topography exceeds height of model domain.'
880                CALL message( 'pcm_init', 'PA0999', 2, 2, 0, 6, 0 )
881             ENDIF
882
883          ENDDO
884       ENDDO
885
886       CALL exchange_horiz_2d_int( pch_index_ji, nys, nyn, nxl, nxr, nbgp )
887
888!
889!--    Initialization of the canopy heat source distribution due to heating
890!--    of the canopy layers by incoming solar radiation, in case that a non-zero
891!--    value is set for the canopy top heat flux (cthf), which equals the
892!--    available net radiation at canopy top.
893!--    The heat source distribution is calculated by a decaying exponential
894!--    function of the downward cumulative leaf area index (cum_lai_hf),
895!--    assuming that the foliage inside the plant canopy is heated by solar
896!--    radiation penetrating the canopy layers according to the distribution
897!--    of net radiation as suggested by Brown & Covey (1966; Agric. Meteorol. 3,
898!--    73–96). This approach has been applied e.g. by Shaw & Schumann (1992;
899!--    Bound.-Layer Meteorol. 61, 47–64).
900!--    When using the urban surface model (USM), canopy heating (pc_heating_rate)
901!--    by radiation is calculated in the USM.
902       IF ( cthf /= 0.0_wp  .AND. .NOT.  urban_surface )  THEN
903
904          ALLOCATE( cum_lai_hf(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                 &
905                    pc_heating_rate(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
906!
907!--       Piecewise calculation of the cumulative leaf area index by vertical
908!--       integration of the leaf area density
909          cum_lai_hf(:,:,:) = 0.0_wp
910          DO  i = nxlg, nxrg
911             DO  j = nysg, nyng
912                DO  k = pch_index_ji(j,i)-1, 0, -1
913                   IF ( k == pch_index_ji(j,i)-1 )  THEN
914                      cum_lai_hf(k,j,i) = cum_lai_hf(k+1,j,i) +                &
915                         ( 0.5_wp * lad_s(k+1,j,i) *                           &
916                           ( zw(k+1) - zu(k+1) ) )  +                          &
917                         ( 0.5_wp * ( 0.5_wp * ( lad_s(k+1,j,i) +              &
918                                                 lad_s(k,j,i) ) +              &
919                                      lad_s(k+1,j,i) ) *                       &
920                           ( zu(k+1) - zw(k) ) ) 
921                   ELSE
922                      cum_lai_hf(k,j,i) = cum_lai_hf(k+1,j,i) +                &
923                         ( 0.5_wp * ( 0.5_wp * ( lad_s(k+2,j,i) +              &
924                                                 lad_s(k+1,j,i) ) +            &
925                                      lad_s(k+1,j,i) ) *                       &
926                           ( zw(k+1) - zu(k+1) ) )  +                          &
927                         ( 0.5_wp * ( 0.5_wp * ( lad_s(k+1,j,i) +              &
928                                                 lad_s(k,j,i) ) +              &
929                                      lad_s(k+1,j,i) ) *                       &
930                           ( zu(k+1) - zw(k) ) )
931                   ENDIF
932                ENDDO
933             ENDDO
934          ENDDO
935
936!           
937!--       In areas with canopy the surface value of the canopy heat
938!--       flux distribution overrides the surface heat flux (shf)
939!--       Start with default surface type
940          DO  m = 1, surf_def_h(0)%ns
941             k = surf_def_h(0)%k(m)
942             IF ( cum_lai_hf(0,j,i) /= 0.0_wp )                                &
943                surf_def_h(0)%shf(m) = cthf * exp( -ext_coef * cum_lai_hf(0,j,i) )
944          ENDDO
945!
946!--       Natural surfaces
947          DO  m = 1, surf_lsm_h%ns
948             k = surf_lsm_h%k(m)
949             IF ( cum_lai_hf(0,j,i) /= 0.0_wp )                                &
950                surf_lsm_h%shf(m) = cthf * exp( -ext_coef * cum_lai_hf(0,j,i) )
951          ENDDO
952!
953!--       Urban surfaces
954          DO  m = 1, surf_usm_h%ns
955             k = surf_usm_h%k(m)
956             IF ( cum_lai_hf(0,j,i) /= 0.0_wp )                                &
957                surf_usm_h%shf(m) = cthf * exp( -ext_coef * cum_lai_hf(0,j,i) )
958          ENDDO
959!
960!
961!--       Calculation of the heating rate (K/s) within the different layers of
962!--       the plant canopy. Calculation is only necessary in areas covered with
963!--       canopy.
964!--       Within the different canopy layers the plant-canopy heating
965!--       rate (pc_heating_rate) is calculated as the vertical
966!--       divergence of the canopy heat fluxes at the top and bottom
967!--       of the respective layer
968          DO  i = nxlg, nxrg
969             DO  j = nysg, nyng
970                DO  k = 1, pch_index_ji(j,i)
971                   IF ( cum_lai_hf(0,j,i) /= 0.0_wp )  THEN
972                      pc_heating_rate(k,j,i) = cthf *                          &
973                                ( exp(-ext_coef*cum_lai_hf(k,j,i)) -           &
974                                  exp(-ext_coef*cum_lai_hf(k-1,j,i) ) ) / dzw(k)
975                   ENDIF
976                ENDDO
977             ENDDO
978          ENDDO
979
980       ENDIF
981!
982!--    Allocate transpiration rate
983       IF ( humidity )                                                         &
984          ALLOCATE( pc_transpiration_rate(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
985
986
987
988    END SUBROUTINE pcm_init
989
990
991!------------------------------------------------------------------------------!
992! Description:
993! ------------
994!> Parin for &plant_canopy_parameters for plant canopy model
995!------------------------------------------------------------------------------!
996    SUBROUTINE pcm_parin
997
998       USE control_parameters,                                                 &
999           ONLY:  message_string, plant_canopy
1000
1001       IMPLICIT NONE
1002
1003       CHARACTER (LEN=80) ::  line  !< dummy string that contains the current line of the parameter file
1004       
1005       NAMELIST /plant_canopy_parameters/                                      &
1006                                  alpha_lad, beta_lad, canopy_drag_coeff,      &
1007                                  canopy_mode, cthf,                           &
1008                                  lad_surface, lad_type_coef,                  & 
1009                                  lad_vertical_gradient,                       &
1010                                  lad_vertical_gradient_level,                 &
1011                                  lai_beta,                                    &
1012                                  leaf_scalar_exch_coeff,                      &
1013                                  leaf_surface_conc, pch_index
1014
1015       NAMELIST /canopy_par/      alpha_lad, beta_lad, canopy_drag_coeff,      &
1016                                  canopy_mode, cthf,                           &
1017                                  lad_surface, lad_type_coef,                  & 
1018                                  lad_vertical_gradient,                       &
1019                                  lad_vertical_gradient_level,                 &
1020                                  lai_beta,                                    &
1021                                  leaf_scalar_exch_coeff,                      &
1022                                  leaf_surface_conc, pch_index
1023                                 
1024       line = ' '
1025       
1026!
1027!--    Try to find radiation model package
1028       REWIND ( 11 )
1029       line = ' '
1030       DO   WHILE ( INDEX( line, '&plant_canopy_parameters' ) == 0 )
1031          READ ( 11, '(A)', END=10 )  line
1032       ENDDO
1033       BACKSPACE ( 11 )
1034
1035!
1036!--    Read user-defined namelist
1037       READ ( 11, plant_canopy_parameters )
1038
1039!
1040!--    Set flag that indicates that the radiation model is switched on
1041       plant_canopy = .TRUE.
1042       
1043       GOTO 12
1044!
1045!--    Try to find old namelist
1046 10    REWIND ( 11 )
1047       line = ' '
1048       DO   WHILE ( INDEX( line, '&canopy_par' ) == 0 )
1049          READ ( 11, '(A)', END=12 )  line
1050       ENDDO
1051       BACKSPACE ( 11 )
1052
1053!
1054!--    Read user-defined namelist
1055       READ ( 11, canopy_par )
1056
1057       message_string = 'namelist canopy_par is deprecated and will be ' // &
1058                     'removed in near future. Please use namelist ' //      &
1059                     'plant_canopy_parameters instead'
1060       CALL message( 'pcm_parin', 'PA0487', 0, 1, 0, 6, 0 )
1061       
1062!
1063!--    Set flag that indicates that the radiation model is switched on
1064       plant_canopy = .TRUE.
1065
1066 12    CONTINUE
1067       
1068
1069    END SUBROUTINE pcm_parin
1070
1071
1072
1073!------------------------------------------------------------------------------!
1074! Description:
1075! ------------
1076!
1077!> Loads 3D plant canopy data from file. File format is as follows:
1078!>
1079!> num_levels
1080!> dtype,x,y,pctype,value(nzb),value(nzb+1), ... ,value(nzb+num_levels-1)
1081!> dtype,x,y,pctype,value(nzb),value(nzb+1), ... ,value(nzb+num_levels-1)
1082!> dtype,x,y,pctype,value(nzb),value(nzb+1), ... ,value(nzb+num_levels-1)
1083!> ...
1084!>
1085!> i.e. first line determines number of levels and further lines represent plant
1086!> canopy data, one line per column and variable. In each data line,
1087!> dtype represents variable to be set:
1088!>
1089!> dtype=1: leaf area density (lad_s)
1090!> dtype=2....n: some additional plant canopy input data quantity
1091!>
1092!> Zeros are added automatically above num_levels until top of domain.  Any
1093!> non-specified (x,y) columns have zero values as default.
1094!------------------------------------------------------------------------------!
1095    SUBROUTINE pcm_read_plant_canopy_3d
1096   
1097       USE control_parameters,                                                 &
1098           ONLY:  coupling_char, message_string
1099
1100       USE indices,                                                            &
1101           ONLY:  nbgp
1102           
1103       IMPLICIT NONE
1104
1105       INTEGER(iwp)                        ::  dtype     !< type of input data (1=lad)
1106       INTEGER(iwp)                        ::  pctype    !< type of plant canopy (deciduous,non-deciduous,...)
1107       INTEGER(iwp)                        ::  i, j      !< running index
1108       INTEGER(iwp)                        ::  nzp       !< number of vertical layers of plant canopy
1109       
1110       REAL(wp), DIMENSION(:), ALLOCATABLE ::  col   !< vertical column of input data
1111
1112!
1113!--    Initialize lad_s array
1114       lad_s = 0.0_wp
1115       
1116!
1117!--    Open and read plant canopy input data
1118       OPEN(152, FILE='PLANT_CANOPY_DATA_3D' // TRIM( coupling_char ),         &
1119                 ACCESS='SEQUENTIAL', ACTION='READ', STATUS='OLD',             &
1120                 FORM='FORMATTED', ERR=515)
1121       READ(152, *, ERR=516, END=517)  nzp   !< read first line = number of vertical layers
1122       
1123       ALLOCATE( col(0:nzp-1) )
1124
1125       DO
1126          READ(152, *, ERR=516, END=517) dtype, i, j, pctype, col(:)
1127          IF ( i < nxlg  .OR.  i > nxrg  .OR.  j < nysg  .OR.  j > nyng )  CYCLE
1128         
1129          SELECT CASE (dtype)
1130             CASE( 1 )   !< leaf area density
1131!
1132!--             This is just the pure canopy layer assumed to be grounded to
1133!--             a flat domain surface. At locations where plant canopy sits
1134!--             on top of any kind of topography, the vertical plant column
1135!--             must be "lifted", which is done in SUBROUTINE pcm_tendency.           
1136                IF ( pctype < 0  .OR.  pctype > 10 )  THEN   !< incorrect plant canopy type
1137                   WRITE( message_string, * ) 'Incorrect type of plant canopy. '   //  &
1138                                              'Allowed values 0 <= pctype <= 10, ' //  &
1139                                              'but pctype is ', pctype
1140                   CALL message( 'pcm_read_plant_canopy_3d', 'PA0349', 1, 2, 0, 6, 0 )
1141                ENDIF
1142                lad_s(0:nzp-1,j,i) = col(0:nzp-1) * lad_type_coef(pctype)
1143               
1144             CASE DEFAULT
1145                WRITE(message_string, '(a,i2,a)')   &
1146                     'Unknown record type in file PLANT_CANOPY_DATA_3D: "', dtype, '"'
1147                CALL message( 'pcm_read_plant_canopy_3d', 'PA0530', 1, 2, 0, 6, 0 )
1148          END SELECT
1149       ENDDO
1150
1151515    message_string = 'error opening file PLANT_CANOPY_DATA_3D'
1152       CALL message( 'pcm_read_plant_canopy_3d', 'PA0531', 1, 2, 0, 6, 0 )
1153
1154516    message_string = 'error reading file PLANT_CANOPY_DATA_3D'
1155       CALL message( 'pcm_read_plant_canopy_3d', 'PA0532', 1, 2, 0, 6, 0 )
1156
1157517    CLOSE(152)
1158       DEALLOCATE( col )
1159       
1160       CALL exchange_horiz( lad_s, nbgp )
1161       
1162    END SUBROUTINE pcm_read_plant_canopy_3d
1163   
1164   
1165
1166!------------------------------------------------------------------------------!
1167! Description:
1168! ------------
1169!> Calculation of the tendency terms, accounting for the effect of the plant
1170!> canopy on momentum and scalar quantities.
1171!>
1172!> The canopy is located where the leaf area density lad_s(k,j,i) > 0.0
1173!> (defined on scalar grid), as initialized in subroutine pcm_init.
1174!> The lad on the w-grid is vertically interpolated from the surrounding
1175!> lad_s. The upper boundary of the canopy is defined on the w-grid at
1176!> k = pch_index. Here, the lad is zero.
1177!>
1178!> The canopy drag must be limited (previously accounted for by calculation of
1179!> a limiting canopy timestep for the determination of the maximum LES timestep
1180!> in subroutine timestep), since it is physically impossible that the canopy
1181!> drag alone can locally change the sign of a velocity component. This
1182!> limitation is realized by calculating preliminary tendencies and velocities.
1183!> It is subsequently checked if the preliminary new velocity has a different
1184!> sign than the current velocity. If so, the tendency is limited in a way that
1185!> the velocity can at maximum be reduced to zero by the canopy drag.
1186!>
1187!>
1188!> Call for all grid points
1189!------------------------------------------------------------------------------!
1190    SUBROUTINE pcm_tendency( component )
1191
1192
1193       USE control_parameters,                                                 &
1194           ONLY:  dt_3d, message_string
1195
1196       USE kinds
1197
1198       IMPLICIT NONE
1199
1200       INTEGER(iwp) ::  component !< prognostic variable (u,v,w,pt,q,e)
1201       INTEGER(iwp) ::  i         !< running index
1202       INTEGER(iwp) ::  j         !< running index
1203       INTEGER(iwp) ::  k         !< running index
1204       INTEGER(iwp) ::  k_wall    !< vertical index of topography top
1205       INTEGER(iwp) ::  kk        !< running index for flat lad arrays
1206
1207       REAL(wp) ::  ddt_3d    !< inverse of the LES timestep (dt_3d)
1208       REAL(wp) ::  lad_local !< local lad value
1209       REAL(wp) ::  pre_tend  !< preliminary tendency
1210       REAL(wp) ::  pre_u     !< preliminary u-value
1211       REAL(wp) ::  pre_v     !< preliminary v-value
1212       REAL(wp) ::  pre_w     !< preliminary w-value
1213
1214
1215       ddt_3d = 1.0_wp / dt_3d
1216 
1217!
1218!--    Compute drag for the three velocity components and the SGS-TKE:
1219       SELECT CASE ( component )
1220
1221!
1222!--       u-component
1223          CASE ( 1 )
1224             DO  i = nxlu, nxr
1225                DO  j = nys, nyn
1226!
1227!--                Determine topography-top index on u-grid
1228                   k_wall = get_topography_top_index_ji( j, i, 'u' )
1229                   DO  k = k_wall+1, k_wall + pch_index_ji(j,i)
1230
1231                      kk = k - k_wall   !- lad arrays are defined flat
1232!
1233!--                   In order to create sharp boundaries of the plant canopy,
1234!--                   the lad on the u-grid at index (k,j,i) is equal to
1235!--                   lad_s(k,j,i), rather than being interpolated from the
1236!--                   surrounding lad_s, because this would yield smaller lad
1237!--                   at the canopy boundaries than inside of the canopy.
1238!--                   For the same reason, the lad at the rightmost(i+1)canopy
1239!--                   boundary on the u-grid equals lad_s(k,j,i).
1240                      lad_local = lad_s(kk,j,i)
1241                      IF ( lad_local == 0.0_wp .AND. lad_s(kk,j,i-1) > 0.0_wp )&
1242                      THEN
1243                         lad_local = lad_s(kk,j,i-1)
1244                      ENDIF
1245
1246                      pre_tend = 0.0_wp
1247                      pre_u = 0.0_wp
1248!
1249!--                   Calculate preliminary value (pre_tend) of the tendency
1250                      pre_tend = - cdc *                                       &
1251                                   lad_local *                                 &
1252                                   SQRT( u(k,j,i)**2 +                         &
1253                                         ( 0.25_wp * ( v(k,j,i-1) +            &
1254                                                       v(k,j,i)   +            &
1255                                                       v(k,j+1,i) +            &
1256                                                       v(k,j+1,i-1) )          &
1257                                         )**2 +                                &
1258                                         ( 0.25_wp * ( w(k-1,j,i-1) +          &
1259                                                       w(k-1,j,i)   +          &
1260                                                       w(k,j,i-1)   +          &
1261                                                       w(k,j,i) )              &
1262                                         )**2                                  &
1263                                       ) *                                     &
1264                                   u(k,j,i)
1265
1266!
1267!--                   Calculate preliminary new velocity, based on pre_tend
1268                      pre_u = u(k,j,i) + dt_3d * pre_tend
1269!
1270!--                   Compare sign of old velocity and new preliminary velocity,
1271!--                   and in case the signs are different, limit the tendency
1272                      IF ( SIGN(pre_u,u(k,j,i)) /= pre_u )  THEN
1273                         pre_tend = - u(k,j,i) * ddt_3d
1274                      ELSE
1275                         pre_tend = pre_tend
1276                      ENDIF
1277!
1278!--                   Calculate final tendency
1279                      tend(k,j,i) = tend(k,j,i) + pre_tend
1280
1281                   ENDDO
1282                ENDDO
1283             ENDDO
1284
1285!
1286!--       v-component
1287          CASE ( 2 )
1288             DO  i = nxl, nxr
1289                DO  j = nysv, nyn
1290!
1291!--                Determine topography-top index on v-grid
1292                   k_wall = get_topography_top_index_ji( j, i, 'v' )
1293
1294                   DO  k = k_wall+1, k_wall + pch_index_ji(j,i)
1295
1296                      kk = k - k_wall   !- lad arrays are defined flat
1297!
1298!--                   In order to create sharp boundaries of the plant canopy,
1299!--                   the lad on the v-grid at index (k,j,i) is equal to
1300!--                   lad_s(k,j,i), rather than being interpolated from the
1301!--                   surrounding lad_s, because this would yield smaller lad
1302!--                   at the canopy boundaries than inside of the canopy.
1303!--                   For the same reason, the lad at the northmost(j+1) canopy
1304!--                   boundary on the v-grid equals lad_s(k,j,i).
1305                      lad_local = lad_s(kk,j,i)
1306                      IF ( lad_local == 0.0_wp .AND. lad_s(kk,j-1,i) > 0.0_wp )&
1307                      THEN
1308                         lad_local = lad_s(kk,j-1,i)
1309                      ENDIF
1310
1311                      pre_tend = 0.0_wp
1312                      pre_v = 0.0_wp
1313!
1314!--                   Calculate preliminary value (pre_tend) of the tendency
1315                      pre_tend = - cdc *                                       &
1316                                   lad_local *                                 &
1317                                   SQRT( ( 0.25_wp * ( u(k,j-1,i)   +          &
1318                                                       u(k,j-1,i+1) +          &
1319                                                       u(k,j,i)     +          &
1320                                                       u(k,j,i+1) )            &
1321                                         )**2 +                                &
1322                                         v(k,j,i)**2 +                         &
1323                                         ( 0.25_wp * ( w(k-1,j-1,i) +          &
1324                                                       w(k-1,j,i)   +          &
1325                                                       w(k,j-1,i)   +          &
1326                                                       w(k,j,i) )              &
1327                                         )**2                                  &
1328                                       ) *                                     &
1329                                   v(k,j,i)
1330
1331!
1332!--                   Calculate preliminary new velocity, based on pre_tend
1333                      pre_v = v(k,j,i) + dt_3d * pre_tend
1334!
1335!--                   Compare sign of old velocity and new preliminary velocity,
1336!--                   and in case the signs are different, limit the tendency
1337                      IF ( SIGN(pre_v,v(k,j,i)) /= pre_v )  THEN
1338                         pre_tend = - v(k,j,i) * ddt_3d
1339                      ELSE
1340                         pre_tend = pre_tend
1341                      ENDIF
1342!
1343!--                   Calculate final tendency
1344                      tend(k,j,i) = tend(k,j,i) + pre_tend
1345
1346                   ENDDO
1347                ENDDO
1348             ENDDO
1349
1350!
1351!--       w-component
1352          CASE ( 3 )
1353             DO  i = nxl, nxr
1354                DO  j = nys, nyn
1355!
1356!--                Determine topography-top index on w-grid
1357                   k_wall = get_topography_top_index_ji( j, i, 'w' )
1358
1359                   DO  k = k_wall+1, k_wall + pch_index_ji(j,i) - 1
1360
1361                      kk = k - k_wall   !- lad arrays are defined flat
1362
1363                      pre_tend = 0.0_wp
1364                      pre_w = 0.0_wp
1365!
1366!--                   Calculate preliminary value (pre_tend) of the tendency
1367                      pre_tend = - cdc *                                       &
1368                                   (0.5_wp *                                   &
1369                                      ( lad_s(kk+1,j,i) + lad_s(kk,j,i) )) *   &
1370                                   SQRT( ( 0.25_wp * ( u(k,j,i)   +            &
1371                                                       u(k,j,i+1) +            &
1372                                                       u(k+1,j,i) +            &
1373                                                       u(k+1,j,i+1) )          &
1374                                         )**2 +                                &
1375                                         ( 0.25_wp * ( v(k,j,i)   +            &
1376                                                       v(k,j+1,i) +            &
1377                                                       v(k+1,j,i) +            &
1378                                                       v(k+1,j+1,i) )          &
1379                                         )**2 +                                &
1380                                         w(k,j,i)**2                           &
1381                                       ) *                                     &
1382                                   w(k,j,i)
1383!
1384!--                   Calculate preliminary new velocity, based on pre_tend
1385                      pre_w = w(k,j,i) + dt_3d * pre_tend
1386!
1387!--                   Compare sign of old velocity and new preliminary velocity,
1388!--                   and in case the signs are different, limit the tendency
1389                      IF ( SIGN(pre_w,w(k,j,i)) /= pre_w )  THEN
1390                         pre_tend = - w(k,j,i) * ddt_3d
1391                      ELSE
1392                         pre_tend = pre_tend
1393                      ENDIF
1394!
1395!--                   Calculate final tendency
1396                      tend(k,j,i) = tend(k,j,i) + pre_tend
1397
1398                   ENDDO
1399                ENDDO
1400             ENDDO
1401
1402!
1403!--       potential temperature
1404          CASE ( 4 )
1405             DO  i = nxl, nxr
1406                DO  j = nys, nyn
1407!
1408!--                Determine topography-top index on scalar-grid
1409                   k_wall = get_topography_top_index_ji( j, i, 's' )
1410
1411                   DO  k = k_wall+1, k_wall + pch_index_ji(j,i)
1412
1413                      kk = k - k_wall   !- lad arrays are defined flat
1414                      tend(k,j,i) = tend(k,j,i) + pc_heating_rate(kk,j,i)
1415                   ENDDO
1416                ENDDO
1417             ENDDO
1418
1419!
1420!--       humidity
1421          CASE ( 5 )
1422             DO  i = nxl, nxr
1423                DO  j = nys, nyn
1424!
1425!--                Determine topography-top index on scalar-grid
1426                   k_wall = get_topography_top_index_ji( j, i, 's' )
1427
1428                   DO  k = k_wall+1, k_wall + pch_index_ji(j,i)
1429
1430                      kk = k - k_wall   !- lad arrays are defined flat
1431                      pc_transpiration_rate(kk,j,i) =  - lsec                  &
1432                                       * lad_s(kk,j,i) *                       &
1433                                       SQRT( ( 0.5_wp * ( u(k,j,i) +           &
1434                                                          u(k,j,i+1) )         &
1435                                             )**2 +                            &
1436                                             ( 0.5_wp * ( v(k,j,i) +           &
1437                                                          v(k,j+1,i) )         &
1438                                             )**2 +                            &
1439                                             ( 0.5_wp * ( w(k-1,j,i) +         & 
1440                                                          w(k,j,i) )           &
1441                                             )**2                              &
1442                                           ) *                                 &
1443                                       ( q(k,j,i) - lsc )
1444
1445                      tend(k,j,i) = tend(k,j,i) + pc_transpiration_rate(kk,j,i)
1446                   ENDDO
1447                ENDDO
1448             ENDDO
1449
1450!
1451!--       sgs-tke
1452          CASE ( 6 )
1453             DO  i = nxl, nxr
1454                DO  j = nys, nyn
1455!
1456!--                Determine topography-top index on scalar-grid
1457                   k_wall = get_topography_top_index_ji( j, i, 's' )
1458
1459                   DO  k = k_wall+1, k_wall + pch_index_ji(j,i)
1460
1461                      kk = k - k_wall   !- lad arrays are defined flat
1462                      tend(k,j,i) = tend(k,j,i) -                              &
1463                                       2.0_wp * cdc *                          &
1464                                       lad_s(kk,j,i) *                         &
1465                                       SQRT( ( 0.5_wp * ( u(k,j,i) +           &
1466                                                          u(k,j,i+1) )         &
1467                                             )**2 +                            &
1468                                             ( 0.5_wp * ( v(k,j,i) +           &
1469                                                          v(k,j+1,i) )         &
1470                                             )**2 +                            &
1471                                             ( 0.5_wp * ( w(k,j,i) +           &
1472                                                          w(k+1,j,i) )         &
1473                                             )**2                              &
1474                                           ) *                                 &
1475                                       e(k,j,i)
1476                   ENDDO
1477                ENDDO
1478             ENDDO 
1479!
1480!--       scalar concentration
1481          CASE ( 7 )
1482             DO  i = nxl, nxr
1483                DO  j = nys, nyn
1484!
1485!--                Determine topography-top index on scalar-grid
1486                   k_wall = get_topography_top_index_ji( j, i, 's' )
1487
1488                   DO  k = k_wall+1, k_wall + pch_index_ji(j,i)
1489
1490                      kk = k - k_wall   !- lad arrays are defined flat
1491                      tend(k,j,i) = tend(k,j,i) -                              &
1492                                       lsec *                                  &
1493                                       lad_s(kk,j,i) *                         &
1494                                       SQRT( ( 0.5_wp * ( u(k,j,i) +           &
1495                                                          u(k,j,i+1) )         &
1496                                             )**2 +                            &
1497                                             ( 0.5_wp * ( v(k,j,i) +           &
1498                                                          v(k,j+1,i) )         &
1499                                             )**2 +                            &
1500                                             ( 0.5_wp * ( w(k-1,j,i) +         & 
1501                                                          w(k,j,i) )           &
1502                                             )**2                              &
1503                                           ) *                                 &
1504                                       ( s(k,j,i) - lsc )
1505                   ENDDO
1506                ENDDO
1507             ENDDO   
1508
1509
1510
1511          CASE DEFAULT
1512
1513             WRITE( message_string, * ) 'wrong component: ', component
1514             CALL message( 'pcm_tendency', 'PA0279', 1, 2, 0, 6, 0 ) 
1515
1516       END SELECT
1517
1518    END SUBROUTINE pcm_tendency
1519
1520
1521!------------------------------------------------------------------------------!
1522! Description:
1523! ------------
1524!> Calculation of the tendency terms, accounting for the effect of the plant
1525!> canopy on momentum and scalar quantities.
1526!>
1527!> The canopy is located where the leaf area density lad_s(k,j,i) > 0.0
1528!> (defined on scalar grid), as initialized in subroutine pcm_init.
1529!> The lad on the w-grid is vertically interpolated from the surrounding
1530!> lad_s. The upper boundary of the canopy is defined on the w-grid at
1531!> k = pch_index. Here, the lad is zero.
1532!>
1533!> The canopy drag must be limited (previously accounted for by calculation of
1534!> a limiting canopy timestep for the determination of the maximum LES timestep
1535!> in subroutine timestep), since it is physically impossible that the canopy
1536!> drag alone can locally change the sign of a velocity component. This
1537!> limitation is realized by calculating preliminary tendencies and velocities.
1538!> It is subsequently checked if the preliminary new velocity has a different
1539!> sign than the current velocity. If so, the tendency is limited in a way that
1540!> the velocity can at maximum be reduced to zero by the canopy drag.
1541!>
1542!>
1543!> Call for grid point i,j
1544!------------------------------------------------------------------------------!
1545    SUBROUTINE pcm_tendency_ij( i, j, component )
1546
1547
1548       USE control_parameters,                                                 &
1549           ONLY:  dt_3d, message_string
1550
1551       USE kinds
1552
1553       IMPLICIT NONE
1554
1555       INTEGER(iwp) ::  component !< prognostic variable (u,v,w,pt,q,e)
1556       INTEGER(iwp) ::  i         !< running index
1557       INTEGER(iwp) ::  j         !< running index
1558       INTEGER(iwp) ::  k         !< running index
1559       INTEGER(iwp) ::  k_wall    !< vertical index of topography top
1560       INTEGER(iwp) ::  kk        !< running index for flat lad arrays
1561
1562       REAL(wp) ::  ddt_3d    !< inverse of the LES timestep (dt_3d)
1563       REAL(wp) ::  lad_local !< local lad value
1564       REAL(wp) ::  pre_tend  !< preliminary tendency
1565       REAL(wp) ::  pre_u     !< preliminary u-value
1566       REAL(wp) ::  pre_v     !< preliminary v-value
1567       REAL(wp) ::  pre_w     !< preliminary w-value
1568
1569
1570       ddt_3d = 1.0_wp / dt_3d
1571!
1572!--    Compute drag for the three velocity components and the SGS-TKE
1573       SELECT CASE ( component )
1574
1575!
1576!--       u-component
1577          CASE ( 1 )
1578!
1579!--          Determine topography-top index on u-grid
1580             k_wall = get_topography_top_index_ji( j, i, 'u' )
1581             DO  k = k_wall + 1, k_wall + pch_index_ji(j,i)
1582
1583                kk = k - k_wall  !- lad arrays are defined flat
1584
1585!
1586!--             In order to create sharp boundaries of the plant canopy,
1587!--             the lad on the u-grid at index (k,j,i) is equal to lad_s(k,j,i),
1588!--             rather than being interpolated from the surrounding lad_s,
1589!--             because this would yield smaller lad at the canopy boundaries
1590!--             than inside of the canopy.
1591!--             For the same reason, the lad at the rightmost(i+1)canopy
1592!--             boundary on the u-grid equals lad_s(k,j,i).
1593                lad_local = lad_s(kk,j,i)
1594                IF ( lad_local == 0.0_wp .AND. lad_s(kk,j,i-1) > 0.0_wp )  THEN
1595                   lad_local = lad_s(kk,j,i-1)
1596                ENDIF
1597
1598                pre_tend = 0.0_wp
1599                pre_u = 0.0_wp
1600!
1601!--             Calculate preliminary value (pre_tend) of the tendency
1602                pre_tend = - cdc *                                             &
1603                             lad_local *                                       &   
1604                             SQRT( u(k,j,i)**2 +                               &
1605                                   ( 0.25_wp * ( v(k,j,i-1)  +                 &
1606                                                 v(k,j,i)    +                 &
1607                                                 v(k,j+1,i)  +                 &
1608                                                 v(k,j+1,i-1) )                &
1609                                   )**2 +                                      &
1610                                   ( 0.25_wp * ( w(k-1,j,i-1) +                &
1611                                                 w(k-1,j,i)   +                &
1612                                                 w(k,j,i-1)   +                &
1613                                                 w(k,j,i) )                    &
1614                                   )**2                                        &
1615                                 ) *                                           &
1616                             u(k,j,i)
1617
1618!
1619!--             Calculate preliminary new velocity, based on pre_tend
1620                pre_u = u(k,j,i) + dt_3d * pre_tend
1621!
1622!--             Compare sign of old velocity and new preliminary velocity,
1623!--             and in case the signs are different, limit the tendency
1624                IF ( SIGN(pre_u,u(k,j,i)) /= pre_u )  THEN
1625                   pre_tend = - u(k,j,i) * ddt_3d
1626                ELSE
1627                   pre_tend = pre_tend
1628                ENDIF
1629!
1630!--             Calculate final tendency
1631                tend(k,j,i) = tend(k,j,i) + pre_tend
1632             ENDDO
1633
1634
1635!
1636!--       v-component
1637          CASE ( 2 )
1638!
1639!--          Determine topography-top index on v-grid
1640             k_wall = get_topography_top_index_ji( j, i, 'v' )
1641
1642             DO  k = k_wall + 1, k_wall + pch_index_ji(j,i)
1643
1644                kk = k - k_wall  !- lad arrays are defined flat
1645!
1646!--             In order to create sharp boundaries of the plant canopy,
1647!--             the lad on the v-grid at index (k,j,i) is equal to lad_s(k,j,i),
1648!--             rather than being interpolated from the surrounding lad_s,
1649!--             because this would yield smaller lad at the canopy boundaries
1650!--             than inside of the canopy.
1651!--             For the same reason, the lad at the northmost(j+1)canopy
1652!--             boundary on the v-grid equals lad_s(k,j,i).
1653                lad_local = lad_s(kk,j,i)
1654                IF ( lad_local == 0.0_wp .AND. lad_s(kk,j-1,i) > 0.0_wp )  THEN
1655                   lad_local = lad_s(kk,j-1,i)
1656                ENDIF
1657
1658                pre_tend = 0.0_wp
1659                pre_v = 0.0_wp
1660!
1661!--             Calculate preliminary value (pre_tend) of the tendency
1662                pre_tend = - cdc *                                             &
1663                             lad_local *                                       &
1664                             SQRT( ( 0.25_wp * ( u(k,j-1,i)   +                &
1665                                                 u(k,j-1,i+1) +                &
1666                                                 u(k,j,i)     +                &
1667                                                 u(k,j,i+1) )                  &
1668                                   )**2 +                                      &
1669                                   v(k,j,i)**2 +                               &
1670                                   ( 0.25_wp * ( w(k-1,j-1,i) +                &
1671                                                 w(k-1,j,i)   +                &
1672                                                 w(k,j-1,i)   +                &
1673                                                 w(k,j,i) )                    &
1674                                   )**2                                        &
1675                                 ) *                                           &
1676                             v(k,j,i)
1677
1678!
1679!--             Calculate preliminary new velocity, based on pre_tend
1680                pre_v = v(k,j,i) + dt_3d * pre_tend
1681!
1682!--             Compare sign of old velocity and new preliminary velocity,
1683!--             and in case the signs are different, limit the tendency
1684                IF ( SIGN(pre_v,v(k,j,i)) /= pre_v )  THEN
1685                   pre_tend = - v(k,j,i) * ddt_3d
1686                ELSE
1687                   pre_tend = pre_tend
1688                ENDIF
1689!
1690!--             Calculate final tendency
1691                tend(k,j,i) = tend(k,j,i) + pre_tend
1692             ENDDO
1693
1694
1695!
1696!--       w-component
1697          CASE ( 3 )
1698!
1699!--          Determine topography-top index on w-grid
1700             k_wall = get_topography_top_index_ji( j, i, 'w' )
1701
1702             DO  k = k_wall + 1, k_wall + pch_index_ji(j,i) - 1
1703
1704                kk = k - k_wall  !- lad arrays are defined flat
1705
1706                pre_tend = 0.0_wp
1707                pre_w = 0.0_wp
1708!
1709!--             Calculate preliminary value (pre_tend) of the tendency
1710                pre_tend = - cdc *                                             &
1711                             (0.5_wp *                                         &
1712                                ( lad_s(kk+1,j,i) + lad_s(kk,j,i) )) *         &
1713                             SQRT( ( 0.25_wp * ( u(k,j,i)    +                 & 
1714                                                 u(k,j,i+1)  +                 &
1715                                                 u(k+1,j,i)  +                 &
1716                                                 u(k+1,j,i+1) )                &
1717                                   )**2 +                                      &
1718                                   ( 0.25_wp * ( v(k,j,i)    +                 &
1719                                                 v(k,j+1,i)  +                 &
1720                                                 v(k+1,j,i)  +                 &
1721                                                 v(k+1,j+1,i) )                &
1722                                   )**2 +                                      &
1723                                   w(k,j,i)**2                                 &
1724                                 ) *                                           &
1725                             w(k,j,i)
1726!
1727!--             Calculate preliminary new velocity, based on pre_tend
1728                pre_w = w(k,j,i) + dt_3d * pre_tend
1729!
1730!--             Compare sign of old velocity and new preliminary velocity,
1731!--             and in case the signs are different, limit the tendency
1732                IF ( SIGN(pre_w,w(k,j,i)) /= pre_w )  THEN
1733                   pre_tend = - w(k,j,i) * ddt_3d
1734                ELSE
1735                   pre_tend = pre_tend
1736                ENDIF
1737!
1738!--             Calculate final tendency
1739                tend(k,j,i) = tend(k,j,i) + pre_tend
1740             ENDDO
1741
1742!
1743!--       potential temperature
1744          CASE ( 4 )
1745!
1746!--          Determine topography-top index on scalar grid
1747             k_wall = get_topography_top_index_ji( j, i, 's' )
1748
1749             DO  k = k_wall + 1, k_wall + pch_index_ji(j,i)
1750                kk = k - k_wall  !- lad arrays are defined flat
1751                tend(k,j,i) = tend(k,j,i) + pc_heating_rate(kk,j,i)
1752             ENDDO
1753
1754
1755!
1756!--       humidity
1757          CASE ( 5 )
1758!
1759!--          Determine topography-top index on scalar grid
1760             k_wall = get_topography_top_index_ji( j, i, 's' )
1761
1762             DO  k = k_wall + 1, k_wall + pch_index_ji(j,i)
1763                kk = k - k_wall  !- lad arrays are defined flat
1764
1765                pc_transpiration_rate(kk,j,i) = - lsec                         &
1766                                 * lad_s(kk,j,i) *                             &
1767                                 SQRT( ( 0.5_wp * ( u(k,j,i) +                 &
1768                                                    u(k,j,i+1) )               &
1769                                       )**2  +                                 &
1770                                       ( 0.5_wp * ( v(k,j,i) +                 &
1771                                                    v(k,j+1,i) )               &
1772                                       )**2 +                                  &
1773                                       ( 0.5_wp * ( w(k-1,j,i) +               &
1774                                                    w(k,j,i) )                 &
1775                                       )**2                                    &
1776                                     ) *                                       &
1777                                 ( q(k,j,i) - lsc )
1778
1779                tend(k,j,i) = tend(k,j,i) + pc_transpiration_rate(kk,j,i)
1780
1781             ENDDO   
1782
1783!
1784!--       sgs-tke
1785          CASE ( 6 )
1786!
1787!--          Determine topography-top index on scalar grid
1788             k_wall = get_topography_top_index_ji( j, i, 's' )
1789
1790             DO  k = k_wall + 1, k_wall + pch_index_ji(j,i)
1791
1792                kk = k - k_wall
1793                tend(k,j,i) = tend(k,j,i) -                                    &
1794                                 2.0_wp * cdc *                                &
1795                                 lad_s(kk,j,i) *                               &
1796                                 SQRT( ( 0.5_wp * ( u(k,j,i) +                 &
1797                                                    u(k,j,i+1) )               &
1798                                       )**2 +                                  & 
1799                                       ( 0.5_wp * ( v(k,j,i) +                 &
1800                                                    v(k,j+1,i) )               &
1801                                       )**2 +                                  &
1802                                       ( 0.5_wp * ( w(k,j,i) +                 &
1803                                                    w(k+1,j,i) )               &
1804                                       )**2                                    &
1805                                     ) *                                       &
1806                                 e(k,j,i)
1807             ENDDO
1808             
1809!
1810!--       scalar concentration
1811          CASE ( 7 )
1812!
1813!--          Determine topography-top index on scalar grid
1814             k_wall = get_topography_top_index_ji( j, i, 's' )
1815
1816             DO  k = k_wall + 1, k_wall + pch_index_ji(j,i)
1817
1818                kk = k - k_wall
1819                tend(k,j,i) = tend(k,j,i) -                                    &
1820                                 lsec *                                        &
1821                                 lad_s(kk,j,i) *                               &
1822                                 SQRT( ( 0.5_wp * ( u(k,j,i) +                 &
1823                                                    u(k,j,i+1) )               &
1824                                       )**2  +                                 &
1825                                       ( 0.5_wp * ( v(k,j,i) +                 &
1826                                                    v(k,j+1,i) )               &
1827                                       )**2 +                                  &
1828                                       ( 0.5_wp * ( w(k-1,j,i) +               &
1829                                                    w(k,j,i) )                 &
1830                                       )**2                                    &
1831                                     ) *                                       &
1832                                 ( s(k,j,i) - lsc )
1833             ENDDO               
1834
1835       CASE DEFAULT
1836
1837          WRITE( message_string, * ) 'wrong component: ', component
1838          CALL message( 'pcm_tendency', 'PA0279', 1, 2, 0, 6, 0 ) 
1839
1840       END SELECT
1841
1842    END SUBROUTINE pcm_tendency_ij
1843
1844
1845
1846 END MODULE plant_canopy_model_mod
Note: See TracBrowser for help on using the repository browser.