source: palm/trunk/SOURCE/print_1d.f90 @ 4186

Last change on this file since 4186 was 4182, checked in by scharf, 5 years ago
  • corrected "Former revisions" section
  • minor formatting in "Former revisions" section
  • added "Author" section
  • Property svn:keywords set to Id
File size: 5.0 KB
Line 
1!> @file print_1d.f90
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2019 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: print_1d.f90 4182 2019-08-22 15:20:23Z suehring $
27! Corrected "Former revisions" section
28!
29! 3655 2019-01-07 16:51:22Z knoop
30! Renamed output variables
31!
32! Revision 1.1  1997/09/19 07:45:22  raasch
33! Initial revision
34!
35!
36! Description:
37! ------------
38!> List output of 1D-profiles.
39!------------------------------------------------------------------------------!
40 SUBROUTINE print_1d
41 
42
43    USE arrays_3d,                                                             &
44        ONLY:  zu, zw
45
46    USE control_parameters,                                                    &
47        ONLY:  run_description_header, simulated_time_chr
48
49    USE cpulog,                                                                &
50        ONLY:  cpu_log, log_point
51
52    USE indices,                                                               &
53        ONLY:  nzb, nzt
54
55    USE kinds
56
57    USE pegrid
58
59    USE statistics,                                                            &
60        ONLY:  flow_statistics_called, hom, region, statistic_regions
61
62    IMPLICIT NONE
63
64
65    CHARACTER (LEN=20) ::  period_chr  !<
66
67    INTEGER(iwp) ::  k   !<
68    INTEGER(iwp) ::  sr  !<
69
70
71!
72!-- If required, compute statistics.
73    IF ( .NOT. flow_statistics_called )  CALL flow_statistics
74
75!
76!-- Flow_statistics has its own cpu-time measuring.
77    CALL cpu_log( log_point(18), 'print_1d', 'start' )
78
79    IF ( myid == 0 )  THEN
80!
81!--    Open file for list output of profiles.
82       CALL check_open( 16 )
83
84!
85!--    Prepare header.
86       period_chr = ' no time-average!'
87
88!
89!--    Output for the total domain (and each subregion, if applicable).
90       DO  sr = 0, statistic_regions
91!
92!--       Write header.
93          WRITE ( 16, 112 )
94          WRITE ( 16, 100 )  TRIM( run_description_header ) // '    ' // &
95                             TRIM( region( sr ) ), TRIM( period_chr ), 'uv'
96          WRITE ( 16, 105 )  TRIM( simulated_time_chr )
97          WRITE ( 16, 111 )
98
99!
100!--       Output of values on the scalar levels.
101          WRITE ( 16, 120 )
102          WRITE ( 16, 111 )
103          DO  k = nzt+1, nzb, -1
104             WRITE ( 16, 121)  k, zu(k), hom(k,1,1,sr),           &
105                               hom(k,1,1,sr) - hom(k,1,5,sr),     &
106                               hom(k,1,2,sr),                     &
107                               hom(k,1,2,sr) - hom(k,1,6,sr),     &
108                               hom(k,1,4,sr),                     &
109                               hom(k,1,4,sr) - hom(k,1,7,sr),     &
110                               hom(k,1,8,sr), hom(k,1,9,sr),      &
111                               hom(k,1,10,sr), hom(k,1,11,sr), zu(k), k
112          ENDDO
113          WRITE ( 16, 111 )
114          WRITE ( 16, 120 )
115          WRITE ( 16, 111 )
116
117!
118!--       Output of values on the w-levels.
119          WRITE ( 16, 112 )
120          WRITE ( 16, 100 )  TRIM( run_description_header ) // '    ' // &
121                             TRIM( region( sr ) ), TRIM( period_chr ), 'w'
122          WRITE ( 16, 105 )  TRIM( simulated_time_chr )
123          WRITE ( 16, 111 )
124
125          WRITE ( 16, 130 )
126          WRITE ( 16, 111 )
127          DO  k = nzt+1, nzb, -1
128             WRITE ( 16, 131)  k, zw(k), hom(k,1,16,sr),            &
129                               hom(k,1,18,sr), hom(k,1,12,sr), &
130                               hom(k,1,19,sr), hom(k,1,14,sr), &
131                               hom(k,1,20,sr), zw(k), k
132          ENDDO
133          WRITE ( 16, 111 )
134          WRITE ( 16, 130 )
135          WRITE ( 16, 111 )
136
137       ENDDO
138
139    ENDIF
140
141    CALL cpu_log( log_point(18), 'print_1d', 'stop' )
142
143!
144!-- Formats.
145100 FORMAT (1X,A/1X,10('-')/ &
146            ' Horizontally',A,' averaged profiles on the ',A,'-level')
147105 FORMAT (' Time: ',A)
148111 FORMAT (1X,131('-'))
149112 FORMAT (/)
150120 FORMAT ('   k     zu      u     du     v     dv     theta dtheta ', &
151            ' e      Km    Kh     l      zu      k')
152121 FORMAT (1X,I4,1X,F7.1,1X,F6.2,1X,F5.2,1X,F6.2,1X,F5.2,2X,F6.2,1X,F5.2, &
153            1X,F7.4,1X,F5.2,1X,F5.2,1X,F6.2,1X,F7.1,2X,I4)
154130 FORMAT ('   k     zw       w''theta''   wtheta     w''u''       wu       ',&
155            '  w''v''       wv        zw      k')
156131 FORMAT (1X,I4,1X,F7.1,6(1X,E10.3),1X,F7.1,2X,I4)
157
158
159 END SUBROUTINE print_1d
Note: See TracBrowser for help on using the repository browser.