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

Last change on this file since 772 was 668, checked in by suehring, 13 years ago

last commit documented

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