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

Last change on this file since 1697 was 1697, checked in by raasch, 8 years ago

FORTRAN an OpenMP errors removed
misplaced cpp-directive fixed
small E- and F-FORMAT changes to avoid informative compiler messages about insufficient field width

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