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

Last change on this file since 1320 was 1320, checked in by raasch, 10 years ago

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

  • Property svn:keywords set to Id
File size: 5.9 KB
RevLine 
[1]1 SUBROUTINE print_1d
2
[1036]3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later 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!
[1310]17! Copyright 1997-2014 Leibniz Universitaet Hannover
[1036]18!--------------------------------------------------------------------------------!
19!
[484]20! Current revisions:
[1]21! -----------------
[1320]22! ONLY-attribute added to USE-statements,
23! kind-parameters added to all INTEGER and REAL declaration statements,
24! kinds are defined in new module kinds,
25! old module precision_kind is removed,
26! revision history before 2012 removed,
27! comment fields (!:) to be used for variable explanations added to
28! all variable declaration statements
[1]29!
30! Former revisions:
31! -----------------
[3]32! $Id: print_1d.f90 1320 2014-03-20 08:40:49Z raasch $
[1037]33!
[1319]34! 1318 2014-03-17 13:35:16Z raasch
35! barrier argument removed from cpu_log,
36! module interfaces removed
37!
[1037]38! 1036 2012-10-22 13:43:42Z raasch
39! code put under GPL (PALM 3.9)
40!
[3]41! RCS Log replace by Id keyword, revision history cleaned up
42!
[1]43! Revision 1.1  1997/09/19 07:45:22  raasch
44! Initial revision
45!
46!
47! Description:
48! ------------
49! List output of 1D-profiles.
50!------------------------------------------------------------------------------!
51
[1320]52    USE arrays_3d,                                                             &
53        ONLY:  zu, zw
54
55    USE control_parameters,                                                    &
56        ONLY:  run_description_header, simulated_time_chr
57
58    USE cpulog,                                                                &
59        ONLY:  cpu_log, log_point
60
61    USE indices,                                                               &
62        ONLY:  nzb, nzt
63
64    USE kinds
65
[1]66    USE pegrid
67
[1320]68    USE statistics,                                                            &
69        ONLY:  flow_statistics_called, hom, region, statistic_regions
70
[1]71    IMPLICIT NONE
72
73
[1320]74    CHARACTER (LEN=20) ::  period_chr  !:
[1]75
[1320]76    INTEGER(iwp) ::  k   !:
77    INTEGER(iwp) ::  sr  !:
[1]78
[1320]79
[1]80!
81!-- If required, compute statistics.
82    IF ( .NOT. flow_statistics_called )  CALL flow_statistics
83
84!
85!-- Flow_statistics has its own cpu-time measuring.
86    CALL cpu_log( log_point(18), 'print_1d', 'start' )
87
88    IF ( myid == 0 )  THEN
89!
90!--    Open file for list output of profiles.
91       CALL check_open( 16 )
92
93!
94!--    Prepare header.
95       period_chr = ' no time-average!'
96
97!
98!--    Output for the total domain (and each subregion, if applicable).
99       DO  sr = 0, statistic_regions
100!
101!--       Write header.
102          WRITE ( 16, 112 )
103          WRITE ( 16, 100 )  TRIM( run_description_header ) // '    ' // &
104                             TRIM( region( sr ) ), TRIM( period_chr ), 'uv'
105          WRITE ( 16, 105 )  TRIM( simulated_time_chr )
106!          ELSE
107!             WRITE ( 16, 106 )  TRIM( simulated_time_chr ),           &
108!                                averaging_interval_pr, average_count_pr
109!          ENDIF
110          WRITE ( 16, 111 )
111
112!
113!--       Output of values on the scalar levels.
114          WRITE ( 16, 120 )
115          WRITE ( 16, 111 )
116          DO  k = nzt+1, nzb, -1
117             WRITE ( 16, 121)  k, zu(k), hom(k,1,1,sr),           &
118                               hom(k,1,1,sr) - hom(k,1,5,sr),     &
119                               hom(k,1,2,sr),                     &
120                               hom(k,1,2,sr) - hom(k,1,6,sr),     &
121                               hom(k,1,4,sr),                     &
122                               hom(k,1,4,sr) - hom(k,1,7,sr),     &
123                               hom(k,1,8,sr), hom(k,1,9,sr),      &
124                               hom(k,1,10,sr), hom(k,1,11,sr), zu(k), k
125          ENDDO
126          WRITE ( 16, 111 )
127          WRITE ( 16, 120 )
128          WRITE ( 16, 111 )
129
130!
131!--       Output of values on the w-levels.
132          WRITE ( 16, 112 )
133          WRITE ( 16, 100 )  TRIM( run_description_header ) // '    ' // &
134                             TRIM( region( sr ) ), TRIM( period_chr ), 'w'
135          WRITE ( 16, 105 )  TRIM( simulated_time_chr )
136!          ELSE
137!             WRITE ( 16, 106 )  TRIM( simulated_time_chr ),           &
138!                                averaging_interval_pr, average_count_pr
139!          ENDIF
140          WRITE ( 16, 111 )
141
142          WRITE ( 16, 130 )
143          WRITE ( 16, 111 )
144          DO  k = nzt+1, nzb, -1
145             WRITE ( 16, 131)  k, zw(k), hom(k,1,16,sr),            &
146                               hom(k,1,18,sr), hom(k,1,12,sr), &
147                               hom(k,1,19,sr), hom(k,1,14,sr), &
148                               hom(k,1,20,sr), zw(k), k
149          ENDDO
150          WRITE ( 16, 111 )
151          WRITE ( 16, 130 )
152          WRITE ( 16, 111 )
153
154       ENDDO
155
156    ENDIF
157
[1318]158    CALL cpu_log( log_point(18), 'print_1d', 'stop' )
[1]159
160!
161!-- Formats.
162100 FORMAT (1X,A/1X,10('-')/ &
163            ' Horizontally',A,' averaged profiles on the ',A,'-level')
164105 FORMAT (' Time: ',A)
165106 FORMAT (' Time: ',A,18X,'averaged over',F7.1,' s (',I4, &
166            ' Single times)')
167111 FORMAT (1X,131('-'))
168112 FORMAT (/)
169120 FORMAT ('   k     zu      u     du     v     dv     pt    dpt    ', &
170            'e      Km    Kh     l      zu      k')
171121 FORMAT (1X,I4,1X,F7.1,1X,F6.2,1X,F5.2,1X,F6.2,1X,F5.2,2X,F6.2,1X,F5.2, &
172            1X,F6.4,1X,F5.2,1X,F5.2,1X,F6.2,1X,F7.1,2X,I4)
173130 FORMAT ('   k     zw      w''pt''     wpt       w''u''      wu       ', &
174            ' w''v''      wv        zw      k')
175131 FORMAT (1X,I4,1X,F7.1,6(1X,E9.3),1X,F7.1,2X,I4)
176
177
178 END SUBROUTINE print_1d
Note: See TracBrowser for help on using the repository browser.