source: palm/tags/release-3.6/SOURCE/user_check_parameters.f90 @ 235

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

preparations for the next release

  • Property svn:keywords set to Id
File size: 2.4 KB
Line 
1 SUBROUTINE user_check_parameters
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: user_check_parameters.f90 226 2009-02-02 07:39:34Z raasch $
11!
12! 217 2008-12-09 18:00:48Z letzel
13! Initial version
14!
15! Description:
16! ------------
17! Check &userpar control parameters and deduce further quantities.
18!------------------------------------------------------------------------------!
19
20    USE control_parameters
21    USE user
22
23    IMPLICIT NONE
24
25!
26!-- In case of non-flat topography, check whether the convention how to
27!-- define the topography grid has been set correctly, or whether the default
28!-- is applicable. If this is not possible, abort.
29    IF ( TRIM( topography ) /= 'flat' )  THEN
30       IF ( TRIM( topography_grid_convention ) == ' ' )  THEN
31          IF ( TRIM( topography ) /= 'single_building' .AND.  &
32               TRIM( topography ) /= 'read_from_file' )  THEN
33!--          The default value is not applicable here, because it is only valid
34!--          for the two standard cases 'single_building' and 'read_from_file'
35!--          defined in init_grid.
36             message_string = 'The value for "topography_grid_convention" '//  &
37                  'is not set. Its default value is & only valid for '//  &
38                  '"topography" = ''single_building'' or ''read_from_file''.'//&
39                  ' & Choose ''cell_edge'' or ''cell_center''.'
40             CALL message( 'user_check_parameters', 'UI0001', 1, 2, 0, 6, 0 )
41          ELSE
42!--          The default value is applicable here.
43!--          Set convention according to topography.
44             IF ( TRIM( topography ) == 'single_building' )  THEN
45                topography_grid_convention = 'cell_edge'
46             ELSEIF ( TRIM( topography ) == 'read_from_file' )  THEN
47                topography_grid_convention = 'cell_center'
48             ENDIF
49          ENDIF
50       ELSEIF ( TRIM( topography_grid_convention ) /= 'cell_edge' .AND.  &
51                TRIM( topography_grid_convention ) /= 'cell_center' )  THEN
52          message_string = 'The value for "topography_grid_convention" is '// &
53               'not recognized. & Choose ''cell_edge'' or ''cell_center''.'
54          CALL message( 'user_check_parameters', 'UI0002', 1, 2, 0, 6, 0 )
55       ENDIF
56    ENDIF
57
58!
59!-- Here the user may add code to check the validity of further &userpar
60!-- control parameters or deduce further quantities.
61
62
63 END SUBROUTINE user_check_parameters
64
Note: See TracBrowser for help on using the repository browser.