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

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

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

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