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

Last change on this file since 2696 was 2696, checked in by kanani, 6 years ago

Merge of branch palm4u into trunk

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