source: palm/trunk/SOURCE/data_output_profiles.f90 @ 4577

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

further re-formatting to follow the PALM coding standard

  • Property svn:keywords set to Id
File size: 12.3 KB
Line 
1!> @file data_output_profiles.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! Current revisions:
20! -----------------
21!
22!
23! Former revisions:
24! -----------------
25! $Id: data_output_profiles.f90 4577 2020-06-25 09:53:58Z raasch $
26! file re-formatted to follow the PALM coding standard
27!
28! 4360 2020-01-07 11:25:50Z suehring
29! Corrected "Former revisions" section
30!
31! 3655 2019-01-07 16:51:22Z knoop
32! add variable description
33!
34! Revision 1.1  1997/09/12 06:28:48  raasch
35! Initial revision
36!
37!
38! Description:
39! ------------
40!> Plot output of 1D-profiles for PROFIL
41!--------------------------------------------------------------------------------------------------!
42 SUBROUTINE data_output_profiles
43
44
45    USE control_parameters,                                                                        &
46        ONLY:  average_count_pr, averaging_interval_pr, coupling_start_time,                       &
47               dopr_n, dopr_time_count, normalizing_region, time_since_reference_point
48
49    USE cpulog,                                                                                    &
50        ONLY:  cpu_log, log_point
51
52    USE indices,                                                                                   &
53        ONLY:  nzb, nzt
54
55    USE kinds
56
57#if defined( __netcdf )
58    USE NETCDF
59#endif
60
61    USE netcdf_interface,                                                                          &
62        ONLY:  id_set_pr, id_var_dopr, id_var_norm_dopr, id_var_time_pr, nc_stat,                  &
63               netcdf_handle_error, output_for_t0
64
65    USE pegrid
66
67    USE profil_parameter
68
69    USE statistics,                                                                                &
70        ONLY:  flow_statistics_called, hom, hom_sum, pr_palm, statistic_regions
71
72    IMPLICIT NONE
73
74
75    INTEGER(iwp) ::  i  !< loop index
76    INTEGER(iwp) ::  sr !< statistic region index
77
78!
79!-- If required, compute statistics
80    IF ( .NOT. flow_statistics_called )  CALL flow_statistics
81
82!
83!-- Flow_statistics has its own CPU time measurement
84    CALL cpu_log( log_point(15), 'data_output_profiles', 'start' )
85
86!
87!-- If required, compute temporal average
88    IF ( averaging_interval_pr == 0.0_wp )  THEN
89       hom_sum(:,:,:) = hom(:,1,:,:)
90    ELSE
91       IF ( average_count_pr > 0 )  THEN
92          hom_sum = hom_sum / REAL( average_count_pr, KIND=wp )
93       ELSE
94!
95!--       This case may happen if dt_dopr is changed in the runtime_parameters-list of a restart run
96          RETURN
97       ENDIF
98    ENDIF
99
100
101    IF ( myid == 0 )  THEN
102
103!
104!--    Plot-output for each (sub-)region
105
106!
107!--    Open file for profile output in NetCDF format
108       CALL check_open( 104 )
109
110!
111!--    Increment the counter for number of output times
112       dopr_time_count = dopr_time_count + 1
113
114!
115!--    Output of initial profiles
116       IF ( dopr_time_count == 1 )  THEN
117
118          IF ( .NOT. output_for_t0 ) THEN
119
120#if defined( __netcdf )
121!
122!--          Store initial time to time axis, but only if an output is required for at least one of
123!--          the profiles. The initial time is either 0, or, in case of a prerun for coupled
124!--          atmosphere-ocean runs, has a negative value
125             DO  i = 1, dopr_n
126                IF ( dopr_initial_index(i) /= 0 )  THEN
127                   nc_stat = NF90_PUT_VAR( id_set_pr, id_var_time_pr,                              &
128                                           (/ -coupling_start_time /),                             &
129                                           start = (/ 1 /), count = (/ 1 /) )
130                   CALL netcdf_handle_error( 'data_output_profiles', 329 )
131                   output_for_t0 = .TRUE.
132                   EXIT
133                ENDIF
134             ENDDO
135
136!
137!--          Store normalization factors
138             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(1), & ! wpt0
139                                     (/ hom_sum(nzb,18,normalizing_region) /),                     &
140                                     start = (/ 1 /), count = (/ 1 /) )
141             CALL netcdf_handle_error( 'data_output_profiles', 330 )
142
143             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(2), & ! ws2
144                                     (/ hom_sum(nzb+8,pr_palm,normalizing_region)**2 /),           &
145                                     start = (/ 1 /), count = (/ 1 /) )
146             CALL netcdf_handle_error( 'data_output_profiles', 331 )
147             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(3), & ! tsw2
148                                     (/ hom_sum(nzb+3,pr_palm,normalizing_region)**2 /),           &
149                                      start = (/ 1 /), count = (/ 1 /) )
150             CALL netcdf_handle_error( 'data_output_profiles', 332 )
151             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(4), & ! ws3
152                                     (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 /),           &
153                                     start = (/ 1 /), count = (/ 1 /) )
154             CALL netcdf_handle_error( 'data_output_profiles', 333 )
155
156             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(5), & ! ws2tsw
157                                     (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 *             &
158                                        hom_sum(nzb+3,pr_palm,normalizing_region)    /),           &
159                                     start = (/ 1 /), count = (/ 1 /) )
160             CALL netcdf_handle_error( 'data_output_profiles', 334 )
161
162             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(6), & ! wstsw2
163                                     (/ hom_sum(nzb+8,pr_palm,normalizing_region) *                &
164                                        hom_sum(nzb+3,pr_palm,normalizing_region)**2 /),           &
165                                     start = (/ 1 /), count = (/ 1 /) )
166             CALL netcdf_handle_error( 'data_output_profiles', 335 )
167
168             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(7), & ! z_i
169                                     (/ hom_sum(nzb+6,pr_palm,normalizing_region) /),              &
170                                     start = (/ 1 /), count = (/ 1 /) )
171             CALL netcdf_handle_error( 'data_output_profiles', 336 )
172
173#endif
174!
175!--          Loop over all 1D variables
176             DO  i = 1, dopr_n
177
178                IF ( dopr_initial_index(i) /= 0 )  THEN
179
180!
181!--                Output for the individual (sub-)regions
182                   DO  sr = 0, statistic_regions
183
184#if defined( __netcdf )
185!
186!--                   Write data to netcdf file
187                      nc_stat = NF90_PUT_VAR( id_set_pr, id_var_dopr(i,sr),                        &
188                                              hom(nzb:nzt+1,1,dopr_initial_index(i),sr),           &
189                                              start = (/ 1, 1 /),                                  &
190                                              count = (/ nzt-nzb+2, 1 /) )
191                      CALL netcdf_handle_error( 'data_output_profiles', 337 )
192#endif
193
194                   ENDDO
195
196                ENDIF   ! Initial profile available
197
198             ENDDO   ! Loop over dopr_n for initial profiles
199
200             IF ( output_for_t0 )  THEN
201                dopr_time_count = dopr_time_count + 1
202             ENDIF
203
204          END IF
205       ENDIF   ! Initial profiles
206
207#if defined( __netcdf )
208
209!
210!--    Store time to time axis
211       nc_stat = NF90_PUT_VAR( id_set_pr, id_var_time_pr,                                          &
212                               (/ time_since_reference_point /),                                   &
213                               start = (/ dopr_time_count /),                                      &
214                               count = (/ 1 /) )
215       CALL netcdf_handle_error( 'data_output_profiles', 338 )
216
217!
218!--    Store normalization factors
219       nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(1), &  ! wpt0
220                               (/ hom_sum(nzb,18,normalizing_region) /),                           &
221                               start = (/ dopr_time_count /),                                      &
222                               count = (/ 1 /) )
223       CALL netcdf_handle_error( 'data_output_profiles', 339 )
224
225       nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(2), &  ! ws2
226                               (/ hom_sum(nzb+8,pr_palm,normalizing_region)**2 /),                 &
227                               start = (/ dopr_time_count /),                                      &
228                               count = (/ 1 /) )
229       CALL netcdf_handle_error( 'data_output_profiles', 340 )
230
231       nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(3), &  ! tsw2
232                               (/ hom_sum(nzb+3,pr_palm,normalizing_region)**2 /),                 &
233                               start = (/ dopr_time_count /),                                      &
234                               count = (/ 1 /) )
235       CALL netcdf_handle_error( 'data_output_profiles', 341 )
236
237       nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(4), &  ! ws3
238                               (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 /),                 &
239                               start = (/ dopr_time_count /),                                      &
240                               count = (/ 1 /) )
241       CALL netcdf_handle_error( 'data_output_profiles', 342 )
242
243       nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(5), &  ! ws2tsw
244                               (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 *                   &
245                                  hom_sum(nzb+3,pr_palm,normalizing_region) /),                    &
246                               start = (/ dopr_time_count /),               &
247                               count = (/ 1 /) )
248       CALL netcdf_handle_error( 'data_output_profiles', 343 )
249
250       nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(6), &  ! wstsw2
251                               (/ hom_sum(nzb+8,pr_palm,normalizing_region) *                      &
252                                  hom_sum(nzb+3,pr_palm,normalizing_region)**2 /),                 &
253                               start = (/ dopr_time_count /),                                      &
254                               count = (/ 1 /) )
255       CALL netcdf_handle_error( 'data_output_profiles', 344 )
256
257       nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(7), &  ! z_i
258                               (/ hom_sum(nzb+6,pr_palm,normalizing_region) /),                    &
259                               start = (/ dopr_time_count /),                                      &
260                               count = (/ 1 /) )
261       CALL netcdf_handle_error( 'data_output_profiles', 345 )
262#endif
263
264!
265!--    Output of the individual (non-initial) profiles
266       DO  i = 1, dopr_n
267
268!
269!--       Output for the individual (sub-)domains
270          DO  sr = 0, statistic_regions
271
272#if defined( __netcdf )
273!
274!--          Write data to netcdf file
275             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_dopr(i,sr),                                 &
276                                     hom_sum(nzb:nzt+1,dopr_index(i),sr),                          &
277                                     start = (/ 1, dopr_time_count /),                             &
278                                     count = (/ nzt-nzb+2, 1 /) )
279             CALL netcdf_handle_error( 'data_output_profiles', 346 )
280#endif
281
282          ENDDO
283
284       ENDDO
285
286    ENDIF  ! Output on PE0
287
288!
289!-- If averaging has been done above, the summation counter must be re-set.
290    IF ( averaging_interval_pr /= 0.0_wp )  THEN
291       average_count_pr = 0
292    ENDIF
293
294    CALL cpu_log( log_point(15), 'data_output_profiles','stop' )
295
296 END SUBROUTINE data_output_profiles
Note: See TracBrowser for help on using the repository browser.