source: palm/tags/release-3.6/SOURCE/user_init_plant_canopy.f90 @ 3979

Last change on this file since 3979 was 226, checked in by raasch, 15 years ago

preparations for the next release

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