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

Last change on this file since 1257 was 1037, checked in by raasch, 11 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 3.3 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-2012  Leibniz University Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23! Former revisions:
24! -----------------
25! $Id: user_init_plant_canopy.f90 1037 2012-10-22 14:10:22Z raasch $
26!
27! 1036 2012-10-22 13:43:42Z raasch
28! code put under GPL (PALM 3.9)
29!
30! 667 2010-12-23 12:06:00Z suehring/gryschka
31! nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng
32!
33! 274 2009-03-26 15:11:21Z heinze
34! Output of messages replaced by message handling routine.
35!
36! 211 2008-11-11 04:46:24Z raasch
37! Former file user_interface.f90 split into one file per subroutine
38!
39! Description:
40! ------------
41! Initialisation of the leaf area density array (for scalar grid points) and
42! the array of the canopy drag coefficient, if the user has not chosen any
43! of the default cases
44!------------------------------------------------------------------------------!
45
46    USE arrays_3d
47    USE control_parameters
48    USE indices
49    USE user
50
51    IMPLICIT NONE
52
53    INTEGER :: i, j 
54
55!
56!-- Here the user-defined grid initializing actions follow:
57
58!
59!-- Set the 3D-arrays lad_s and cdc for user defined canopies
60    SELECT CASE ( TRIM( canopy_mode ) )
61
62       CASE ( 'block' )
63!
64!--       Not allowed here since this is the standard case used in init_3d_model.
65
66       CASE ( 'user_defined_canopy_1' )
67!
68!--       Here the user can define his own topography.
69!--       The following lines contain an example in that the
70!--       plant canopy extends only over the second half of the
71!--       model domain along x
72!          DO  i = nxlg, nxrg
73!             IF ( i >= INT(nx+1/2) ) THEN
74!                DO  j = nysg, nyng
75!                   lad_s(:,j,i) = lad(:)
76!                   cdc(:,j,i)   = drag_coefficient
77!                ENDDO
78!             ELSE
79!                lad_s(:,:,i) = 0.0
80!                cdc(:,:,i)   = 0.0
81!             ENDIF
82!          ENDDO
83!--       After definition, please
84!--       remove the following three lines!
85          message_string = 'canopy_mode "' // canopy_mode // &
86                           '" not available yet'
87          CALL message( 'user_init_plant_canopy', 'UI0007', 0, 1, 0, 6, 0 )
88         
89       CASE DEFAULT
90!
91!--       The DEFAULT case is reached if the parameter canopy_mode contains a
92!--       wrong character string that is neither recognized in init_3d_model nor
93!--       here in user_init_plant_canopy.
94          message_string = 'unknown canopy_mode "' // canopy_mode // '"'
95          CALL message( 'user_init_plant_canopy', 'UI0008', 1, 2, 0, 6, 0 )
96
97    END SELECT
98
99
100 END SUBROUTINE user_init_plant_canopy
101
Note: See TracBrowser for help on using the repository browser.