source: palm/trunk/SOURCE/user_init_grid.f90 @ 256

Last change on this file since 256 was 256, checked in by letzel, 15 years ago
  • topography_grid_convention moved from userpar to inipar
  • documentation and examples updated
  • Property svn:keywords set to Id
File size: 1.9 KB
Line 
1 SUBROUTINE user_init_grid( gls, nzb_local )
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6! add 'single_street_canyon' as standard topography case
7! -topography_grid_convention
8!
9! Former revisions:
10! -----------------
11! $Id: user_init_grid.f90 256 2009-03-08 08:56:27Z letzel $
12!
13! 217 2008-12-09 18:00:48Z letzel
14! +topography_grid_convention
15! Former file user_interface.f90 split into one file per subroutine
16!
17! Description:
18! ------------
19! Execution of user-defined grid initializing actions
20! First argument gls contains the number of ghost layers, which is > 1 if the
21! multigrid method for the pressure solver is used
22!------------------------------------------------------------------------------!
23
24    USE control_parameters
25    USE indices
26    USE user
27
28    IMPLICIT NONE
29
30    INTEGER ::  gls
31
32    INTEGER, DIMENSION(-gls:ny+gls,-gls:nx+gls) ::  nzb_local
33
34!
35!-- Here the user-defined grid initializing actions follow:
36
37!
38!-- Set the index array nzb_local for non-flat topography.
39!-- Here consistency checks concerning domain size and periodicity are necessary
40    SELECT CASE ( TRIM( topography ) )
41
42       CASE ( 'flat', 'single_building', 'single_street_canyon' )
43!
44!--       Not allowed here since these are the standard cases used in init_grid.
45
46       CASE ( 'user_defined_topography_1' )
47!
48!--       Here the user can define his own topography.
49!--       After definition, please remove the following three lines!
50          PRINT*, '+++ user_init_grid: topography "', &
51               topography, '" not available yet'
52          CALL local_stop
53
54       CASE DEFAULT
55!
56!--       The DEFAULT case is reached if the parameter topography contains a
57!--       wrong character string that is neither recognized in init_grid nor
58!--       here in user_init_grid.
59          PRINT*, '+++ (user_)init_grid: unknown topography "', &
60               topography, '"'
61          CALL local_stop
62
63    END SELECT
64
65
66 END SUBROUTINE user_init_grid
67
Note: See TracBrowser for help on using the repository browser.