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

Last change on this file since 2000 was 2000, checked in by knoop, 8 years ago

Forced header and separation lines into 80 columns

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