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

Last change on this file since 4725 was 4649, checked in by raasch, 4 years ago

files re-formatted to follow the PALM coding standard

  • Property svn:keywords set to Id
File size: 5.9 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 terms of the GNU General
6! Public License as published by the Free Software Foundation, either version 3 of the License, or
7! (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
11! Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with PALM. If not, see
14! <http://www.gnu.org/licenses/>.
15!
16! Copyright 1997-2020 Leibniz Universitaet Hannover
17!--------------------------------------------------------------------------------------------------!
18!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: print_1d.f90 4649 2020-08-25 12:11:17Z suehring $
27! File re-formatted to follow the PALM coding standard
28!
29!
30! 4360 2020-01-07 11:25:50Z suehring
31! Corrected "Former revisions" section
32!
33! 3655 2019-01-07 16:51:22Z knoop
34! Renamed output variables
35!
36! Revision 1.1  1997/09/19 07:45:22  raasch
37! Initial revision
38!
39!--------------------------------------------------------------------------------------------------!
40! Description:
41! ------------
42!> List output of 1D-profiles.
43!--------------------------------------------------------------------------------------------------!
44 SUBROUTINE print_1d
45
46
47    USE arrays_3d,                                                                                 &
48        ONLY:  zu,                                                                                 &
49               zw
50
51    USE control_parameters,                                                                        &
52        ONLY:  run_description_header,                                                             &
53               simulated_time_chr
54
55    USE cpulog,                                                                                    &
56        ONLY:  cpu_log,                                                                            &
57               log_point
58
59    USE indices,                                                                                   &
60        ONLY:  nzb,                                                                                &
61               nzt
62
63    USE kinds
64
65    USE pegrid
66
67    USE statistics,                                                                                &
68        ONLY:  flow_statistics_called,                                                             &
69               hom,                                                                                &
70               region,                                                                             &
71               statistic_regions
72
73    IMPLICIT NONE
74
75
76    CHARACTER(LEN=20) ::  period_chr  !<
77
78    INTEGER(iwp) ::  k   !<
79    INTEGER(iwp) ::  sr  !<
80
81
82!
83!-- If required, compute statistics.
84    IF ( .NOT. flow_statistics_called )  CALL flow_statistics
85
86!
87!-- Flow_statistics has its own cpu-time measuring.
88    CALL cpu_log( log_point(18), 'print_1d', 'start' )
89
90    IF ( myid == 0 )  THEN
91!
92!--    Open file for list output of profiles.
93       CALL check_open( 16 )
94
95!
96!--    Prepare header.
97       period_chr = ' no time-average!'
98
99!
100!--    Output for the total domain (and each subregion, if applicable).
101       DO  sr = 0, statistic_regions
102!
103!--       Write header.
104          WRITE( 16, 112 )
105          WRITE( 16, 100 )  TRIM( run_description_header ) // '    ' //                            &
106                            TRIM( region( sr ) ), TRIM( period_chr ), 'uv'
107          WRITE( 16, 105 )  TRIM( simulated_time_chr )
108          WRITE( 16, 111 )
109
110!
111!--       Output of values on the scalar levels.
112          WRITE( 16, 120 )
113          WRITE( 16, 111 )
114          DO  k = nzt+1, nzb, -1
115             WRITE( 16, 121)  k, zu(k), hom(k,1,1,sr), hom(k,1,1,sr) - hom(k,1,5,sr),              &
116                              hom(k,1,2,sr), hom(k,1,2,sr) - hom(k,1,6,sr), hom(k,1,4,sr),         &
117                              hom(k,1,4,sr) - hom(k,1,7,sr), hom(k,1,8,sr), hom(k,1,9,sr),         &
118                              hom(k,1,10,sr), hom(k,1,11,sr), zu(k), k
119          ENDDO
120          WRITE( 16, 111 )
121          WRITE( 16, 120 )
122          WRITE( 16, 111 )
123
124!
125!--       Output of values on the w-levels.
126          WRITE( 16, 112 )
127          WRITE( 16, 100 )  TRIM( run_description_header ) // '    ' //                            &
128                            TRIM( region( sr ) ), TRIM( period_chr ), 'w'
129          WRITE( 16, 105 )  TRIM( simulated_time_chr )
130          WRITE( 16, 111 )
131
132          WRITE( 16, 130 )
133          WRITE( 16, 111 )
134          DO  k = nzt+1, nzb, -1
135             WRITE( 16, 131)  k, zw(k), hom(k,1,16,sr), hom(k,1,18,sr), hom(k,1,12,sr),            &
136                              hom(k,1,19,sr), hom(k,1,14,sr), hom(k,1,20,sr), zw(k), k
137          ENDDO
138          WRITE( 16, 111 )
139          WRITE( 16, 130 )
140          WRITE( 16, 111 )
141
142       ENDDO
143
144    ENDIF
145
146    CALL cpu_log( log_point(18), 'print_1d', 'stop' )
147
148!
149!-- Formats.
150100 FORMAT( 1X, A / 1X, 10( '-' ) / ' Horizontally', A, ' averaged profiles on the ', A, '-level' )
151105 FORMAT( ' Time: ', A )
152111 FORMAT( 1X, 131( '-' ) )
153112 FORMAT( / )
154120 FORMAT( '   k     zu      u     du     v     dv     theta dtheta ',                            &
155            ' e      Km    Kh     l    zu      k' )
156121 FORMAT( 1X, I4, 1X, F7.1, 1X, F6.2, 1X, F5.2, 1X, F6.2, 1X, F5.2, 2X, F6.2, 1X, F5.2, 1X,      &
157            F7.4, 1X, F5.2, 1X, F5.2, 1X, F6.2, 1X, F7.1, 2X, I4 )
158130 FORMAT( '   k     zw       w''theta''   wtheta     w''u''       wu       ',                    &
159            '  w''v''       wv        zw      k' )
160131 FORMAT( 1X, I4, 1X, F7.1, 6( 1X, E10.3 ), 1X, F7.1, 2X, I4 )
161
162
163 END SUBROUTINE print_1d
Note: See TracBrowser for help on using the repository browser.