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

Last change on this file since 4079 was 3655, checked in by knoop, 5 years ago

Bugfix: made "unit" and "found" intend INOUT in module interface subroutines + automatic copyright update

  • Property svn:keywords set to Id
File size: 6.1 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 3655 2019-01-07 16:51:22Z suehring $
27! Renamed output variables
28!
29! 3241 2018-09-12 15:02:00Z raasch
30! unused format statement removed
31!
32! 2718 2018-01-02 08:49:38Z maronga
33! Corrected "Former revisions" section
34!
35! 2696 2017-12-14 17:12:51Z kanani
36! Change in file header (GPL part)
37!
38! 2101 2017-01-05 16:42:31Z suehring
39!
40! 2000 2016-08-20 18:09:15Z knoop
41! Forced header and separation lines into 80 columns
42!
43! 1697 2015-10-28 17:14:10Z raasch
44! small E- and F-FORMAT changes to avoid informative compiler messages about
45! insufficient field width
46!
47! 1682 2015-10-07 23:56:08Z knoop
48! Code annotations made doxygen readable
49!
50! 1320 2014-03-20 08:40:49Z raasch
51! ONLY-attribute added to USE-statements,
52! kind-parameters added to all INTEGER and REAL declaration statements,
53! kinds are defined in new module kinds,
54! old module precision_kind is removed,
55! revision history before 2012 removed,
56! comment fields (!:) to be used for variable explanations added to
57! all variable declaration statements
58!
59! 1318 2014-03-17 13:35:16Z raasch
60! barrier argument removed from cpu_log,
61! module interfaces removed
62!
63! 1036 2012-10-22 13:43:42Z raasch
64! code put under GPL (PALM 3.9)
65!
66! RCS Log replace by Id keyword, revision history cleaned up
67!
68! Revision 1.1  1997/09/19 07:45:22  raasch
69! Initial revision
70!
71!
72! Description:
73! ------------
74!> List output of 1D-profiles.
75!------------------------------------------------------------------------------!
76 SUBROUTINE print_1d
77 
78
79    USE arrays_3d,                                                             &
80        ONLY:  zu, zw
81
82    USE control_parameters,                                                    &
83        ONLY:  run_description_header, simulated_time_chr
84
85    USE cpulog,                                                                &
86        ONLY:  cpu_log, log_point
87
88    USE indices,                                                               &
89        ONLY:  nzb, nzt
90
91    USE kinds
92
93    USE pegrid
94
95    USE statistics,                                                            &
96        ONLY:  flow_statistics_called, hom, region, statistic_regions
97
98    IMPLICIT NONE
99
100
101    CHARACTER (LEN=20) ::  period_chr  !<
102
103    INTEGER(iwp) ::  k   !<
104    INTEGER(iwp) ::  sr  !<
105
106
107!
108!-- If required, compute statistics.
109    IF ( .NOT. flow_statistics_called )  CALL flow_statistics
110
111!
112!-- Flow_statistics has its own cpu-time measuring.
113    CALL cpu_log( log_point(18), 'print_1d', 'start' )
114
115    IF ( myid == 0 )  THEN
116!
117!--    Open file for list output of profiles.
118       CALL check_open( 16 )
119
120!
121!--    Prepare header.
122       period_chr = ' no time-average!'
123
124!
125!--    Output for the total domain (and each subregion, if applicable).
126       DO  sr = 0, statistic_regions
127!
128!--       Write header.
129          WRITE ( 16, 112 )
130          WRITE ( 16, 100 )  TRIM( run_description_header ) // '    ' // &
131                             TRIM( region( sr ) ), TRIM( period_chr ), 'uv'
132          WRITE ( 16, 105 )  TRIM( simulated_time_chr )
133          WRITE ( 16, 111 )
134
135!
136!--       Output of values on the scalar levels.
137          WRITE ( 16, 120 )
138          WRITE ( 16, 111 )
139          DO  k = nzt+1, nzb, -1
140             WRITE ( 16, 121)  k, zu(k), hom(k,1,1,sr),           &
141                               hom(k,1,1,sr) - hom(k,1,5,sr),     &
142                               hom(k,1,2,sr),                     &
143                               hom(k,1,2,sr) - hom(k,1,6,sr),     &
144                               hom(k,1,4,sr),                     &
145                               hom(k,1,4,sr) - hom(k,1,7,sr),     &
146                               hom(k,1,8,sr), hom(k,1,9,sr),      &
147                               hom(k,1,10,sr), hom(k,1,11,sr), zu(k), k
148          ENDDO
149          WRITE ( 16, 111 )
150          WRITE ( 16, 120 )
151          WRITE ( 16, 111 )
152
153!
154!--       Output of values on the w-levels.
155          WRITE ( 16, 112 )
156          WRITE ( 16, 100 )  TRIM( run_description_header ) // '    ' // &
157                             TRIM( region( sr ) ), TRIM( period_chr ), 'w'
158          WRITE ( 16, 105 )  TRIM( simulated_time_chr )
159          WRITE ( 16, 111 )
160
161          WRITE ( 16, 130 )
162          WRITE ( 16, 111 )
163          DO  k = nzt+1, nzb, -1
164             WRITE ( 16, 131)  k, zw(k), hom(k,1,16,sr),            &
165                               hom(k,1,18,sr), hom(k,1,12,sr), &
166                               hom(k,1,19,sr), hom(k,1,14,sr), &
167                               hom(k,1,20,sr), zw(k), k
168          ENDDO
169          WRITE ( 16, 111 )
170          WRITE ( 16, 130 )
171          WRITE ( 16, 111 )
172
173       ENDDO
174
175    ENDIF
176
177    CALL cpu_log( log_point(18), 'print_1d', 'stop' )
178
179!
180!-- Formats.
181100 FORMAT (1X,A/1X,10('-')/ &
182            ' Horizontally',A,' averaged profiles on the ',A,'-level')
183105 FORMAT (' Time: ',A)
184111 FORMAT (1X,131('-'))
185112 FORMAT (/)
186120 FORMAT ('   k     zu      u     du     v     dv     theta dtheta ', &
187            ' e      Km    Kh     l      zu      k')
188121 FORMAT (1X,I4,1X,F7.1,1X,F6.2,1X,F5.2,1X,F6.2,1X,F5.2,2X,F6.2,1X,F5.2, &
189            1X,F7.4,1X,F5.2,1X,F5.2,1X,F6.2,1X,F7.1,2X,I4)
190130 FORMAT ('   k     zw       w''theta''   wtheta     w''u''       wu       ',&
191            '  w''v''       wv        zw      k')
192131 FORMAT (1X,I4,1X,F7.1,6(1X,E10.3),1X,F7.1,2X,I4)
193
194
195 END SUBROUTINE print_1d
Note: See TracBrowser for help on using the repository browser.