source: palm/trunk/SOURCE/user_check_parameters.f90 @ 217

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