source: palm/tags/release-3.6/SOURCE/user_header.f90 @ 1822

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

preparations for the next release

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