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

Last change on this file since 212 was 211, checked in by raasch, 15 years ago

user interface was split into one single file per subroutine

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