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

Last change on this file since 358 was 274, checked in by heinze, 15 years ago

Indentation of the message calls corrected

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