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

Last change on this file since 4180 was 4180, checked in by scharf, 5 years ago

removed comments in 'Former revisions' section that are older than 01.01.2019

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