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

Last change on this file since 354 was 256, checked in by letzel, 15 years ago
  • topography_grid_convention moved from userpar to inipar
  • documentation and examples updated
  • Property svn:keywords set to Id
File size: 1.5 KB
Line 
1 SUBROUTINE user_header( io )
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6! new topography case 'single_street_canyon'
7! topography_grid_convention moved to header
8!
9! Former revisions:
10! -----------------
11! $Id: user_header.f90 256 2009-03-08 08:56:27Z maronga $
12!
13! 2008-12-09 18:00:48Z letzel
14! +topography_grid_convention
15! Former file user_interface.f90 split into one file per subroutine
16!
17! Description:
18! ------------
19! Print a header with user-defined informations.
20!------------------------------------------------------------------------------!
21
22    USE control_parameters
23    USE statistics
24    USE user
25
26    IMPLICIT NONE
27
28    INTEGER ::  i, io
29
30!
31!-- If no user-defined variables are read from the namelist-file, no
32!-- informations will be printed.
33    IF ( .NOT. user_defined_namelist_found )  THEN
34       WRITE ( io, 100 )
35       RETURN
36    ENDIF
37
38!
39!-- Printing the informations.
40    WRITE ( io, 110 )
41
42    IF ( statistic_regions /= 0 )  THEN
43       WRITE ( io, 200 )
44       DO  i = 0, statistic_regions
45          WRITE ( io, 201 )  i, region(i)
46       ENDDO
47    ENDIF
48
49!
50!-- Format-descriptors
51100 FORMAT (//' *** no user-defined variables found'/)
52110 FORMAT (//1X,78('#')                                      &
53            //' User-defined variables and actions:'/  &
54              ' -----------------------------------'//)
55200 FORMAT (' Output of profiles and time series for following regions:' /)
56201 FORMAT (4X,'Region ',I1,':   ',A)
57
58
59 END SUBROUTINE user_header
60
Note: See TracBrowser for help on using the repository browser.