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

Last change on this file since 1343 was 1321, checked in by raasch, 10 years ago

last commit documented

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