source: palm/trunk/SOURCE/user_header.f90 @ 222

Last change on this file since 222 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.1 KB
Line 
1 SUBROUTINE user_header( io )
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6! +topography_grid_convention
7! Former file user_interface.f90 split into one file per subroutine
8!
9! Former revisions:
10! -----------------
11! $Id: user_header.f90 217 2008-12-09 18:00:48Z letzel $
12!
13! Description:
14! ------------
15! Print a header with user-defined informations.
16!------------------------------------------------------------------------------!
17
18    USE control_parameters
19    USE statistics
20    USE user
21
22    IMPLICIT NONE
23
24    INTEGER ::  i, io
25
26!
27!-- If no user-defined variables are read from the namelist-file, no
28!-- informations will be printed.
29    IF ( .NOT. user_defined_namelist_found )  THEN
30       WRITE ( io, 100 )
31       RETURN
32    ENDIF
33
34!
35!-- Printing the informations.
36    WRITE ( io, 110 )
37
38    IF ( statistic_regions /= 0 )  THEN
39       WRITE ( io, 200 )
40       DO  i = 0, statistic_regions
41          WRITE ( io, 201 )  i, region(i)
42       ENDDO
43    ENDIF
44
45    IF ( TRIM( topography ) /= 'flat' )  THEN
46       WRITE ( io, 300 )
47       IF ( TRIM( topography_grid_convention ) == ' ' )  THEN
48          IF ( TRIM( topography ) == 'single_building' )  THEN
49             WRITE ( io, 301 )
50          ELSEIF ( TRIM( topography ) == 'read_from_file' )  THEN
51             WRITE ( io, 302 )
52          ENDIF
53       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_edge' )  THEN
54          WRITE ( io, 301 )
55       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_center' )  THEN
56          WRITE ( io, 302 )
57       ENDIF
58    ENDIF
59
60!
61!-- Format-descriptors
62100 FORMAT (//' *** no user-defined variables found'/)
63110 FORMAT (//1X,78('#')                                      &
64            //' User-defined variables and actions:'/  &
65              ' -----------------------------------'//)
66200 FORMAT (' Output of profiles and time series for following regions:' /)
67201 FORMAT (4X,'Region ',I1,':   ',A)
68300 FORMAT (' Topography grid definition convention:'/)
69301 FORMAT (' cell edge (staggered grid points'/  &
70            ' (u in x-direction, v in y-direction))' /)
71302 FORMAT (' cell center (scalar grid points)' /)
72
73
74 END SUBROUTINE user_header
75
Note: See TracBrowser for help on using the repository browser.