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

Last change on this file since 1538 was 1485, checked in by kanani, 9 years ago

last commit documented

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