source: palm/trunk/SOURCE/user_init_plant_canopy.f90 @ 1484

Last change on this file since 1484 was 1484, checked in by kanani, 10 years ago

New:
---
Subroutine init_plant_canopy added to module plant_canopy_model_mod. (plant_canopy_model)
Alternative method for lad-profile construction added, also, new parameters added.
(header, package_parin, plant_canopy_model, read_var_list, write_var_list)
plant_canopy_model-dependency added to several subroutines. (Makefile)
New package/namelist canopy_par for canopy-related parameters added. (package_parin)

Changed:
---
Code structure of the plant canopy model changed, all canopy-model related code
combined to module plant_canopy_model_mod. (check_parameters, init_3d_model,
modules, timestep)
Module plant_canopy_model_mod added in USE-lists of some subroutines. (check_parameters,
header, init_3d_model, package_parin, read_var_list, user_init_plant_canopy, write_var_list)
Canopy initialization moved to new subroutine init_plant_canopy. (check_parameters,
init_3d_model, plant_canopy_model)
Calculation of canopy timestep-criterion removed, instead, the canopy
drag is now directly limited in the calculation of the canopy tendency terms.
(plant_canopy_model, timestep)
Some parameters renamed. (check_parameters, header, init_plant_canopy,
plant_canopy_model, read_var_list, write_var_list)
Unnecessary 3d-arrays removed. (init_plant_canopy, plant_canopy_model, user_init_plant_canopy)
Parameter checks regarding canopy initialization added. (check_parameters)
All canopy steering parameters moved from namelist inipar to canopy_par. (package_parin, parin)
Some redundant MPI communication removed. (init_plant_canopy)

Bugfix:
---
Missing KIND-attribute for REAL constant added. (check_parameters)
DO-WHILE-loop for lad-profile output restricted. (header)
Removed double-listing of use_upstream_for_tke in ONLY-list of module
control_parameters. (prognostic_equations)

  • Property svn:keywords set to Id
File size: 4.0 KB
Line 
1 SUBROUTINE user_init_plant_canopy
2
3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later 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-2014 Leibniz Universitaet Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22! Changes in the course of the canopy-model modularization:
23!   module plant_canopy_model_mod added,
24!   definition of array cdc (canopy drag coefficient) removed, since it is now
25!   defined purely as a single constant value (see module plant_canopy_model)
26!
27! Former revisions:
28! -----------------
29! $Id: user_init_plant_canopy.f90 1484 2014-10-21 10:53:05Z kanani $
30!
31! 1353 2014-04-08 15:21:23Z heinze
32! REAL constants provided with KIND-attribute
33!
34! 1320 2014-03-20 08:40:49Z raasch
35! kind-parameters added to all INTEGER and REAL declaration statements,
36! kinds are defined in new module kinds,
37! old module precision_kind is removed,
38! revision history before 2012 removed,
39! comment fields (!:) to be used for variable explanations added to
40! all variable declaration statements
41!
42! 1036 2012-10-22 13:43:42Z raasch
43! code put under GPL (PALM 3.9)
44!
45! 211 2008-11-11 04:46:24Z raasch
46! Former file user_interface.f90 split into one file per subroutine
47!
48! Description:
49! ------------
50! Initialisation of the leaf area density array (for scalar grid points) and
51! the array of the canopy drag coefficient, if the user has not chosen any
52! of the default cases
53!------------------------------------------------------------------------------!
54
55    USE arrays_3d
56   
57    USE control_parameters
58   
59    USE indices
60   
61    USE kinds
62
63    USE plant_canopy_model_mod
64   
65    USE user
66
67    IMPLICIT NONE
68
69    INTEGER(iwp) :: i   !: running index
70    INTEGER(iwp) :: j   !: running index
71
72!
73!-- Here the user-defined grid initializing actions follow:
74
75!
76!-- Set the 3D-array lad_s for user defined canopies
77    SELECT CASE ( TRIM( canopy_mode ) )
78
79       CASE ( 'block' )
80!
81!--       Not allowed here since this is the standard case used in init_3d_model.
82
83       CASE ( 'user_defined_canopy_1' )
84!
85!--       Here the user can define his own forest topography.
86!--       The following lines contain an example, where the plant canopy extends
87!--       only over the second half of the model domain along x.
88!--       Attention: DO-loops have to include the ghost points (nxlg-nxrg,
89!--       nysg-nyng), because no exchange of ghost point information is intended,
90!--       in order to minimize communication between CPUs
91!          DO  i = nxlg, nxrg
92!             IF ( i >= INT(nx+1/2) ) THEN
93!                DO  j = nysg, nyng
94!                   lad_s(:,j,i) = lad(:)
95!                ENDDO
96!             ELSE
97!                lad_s(:,:,i) = 0.0_wp
98!             ENDIF
99!          ENDDO
100!
101!--       After definition, please
102!--       remove the following three lines!
103          message_string = 'canopy_mode "' // canopy_mode // &
104                           '" not available yet'
105          CALL message( 'user_init_plant_canopy', 'UI0007', 0, 1, 0, 6, 0 )
106         
107       CASE DEFAULT
108!
109!--       The DEFAULT case is reached if the parameter canopy_mode contains a
110!--       wrong character string that is neither recognized in init_3d_model nor
111!--       here in user_init_plant_canopy.
112          message_string = 'unknown canopy_mode "' // canopy_mode // '"'
113          CALL message( 'user_init_plant_canopy', 'UI0008', 1, 2, 0, 6, 0 )
114
115    END SELECT
116
117
118 END SUBROUTINE user_init_plant_canopy
119
Note: See TracBrowser for help on using the repository browser.