1 | SUBROUTINE data_output_profiles |
---|
2 | |
---|
3 | !------------------------------------------------------------------------------! |
---|
4 | ! Actual revisions: |
---|
5 | ! ----------------- |
---|
6 | ! |
---|
7 | ! |
---|
8 | ! Former revisions: |
---|
9 | ! ----------------- |
---|
10 | ! $Log: data_output_profiles.f90,v $ |
---|
11 | ! Revision 1.18 2006/08/16 14:27:04 raasch |
---|
12 | ! PRINT* statements for testing removed |
---|
13 | ! |
---|
14 | ! Revision 1.17 2006/08/08 12:45:47 raasch |
---|
15 | ! Immediate return in case of average_count_pr = 0. |
---|
16 | ! |
---|
17 | ! Revision 1.16 2006/02/23 10:26:53 raasch |
---|
18 | ! Former routine plot_1d renamed data_output_profiles |
---|
19 | ! pl.. renamed do.., .._anz renamed .._no |
---|
20 | ! error number argument for handle_netcdf_error |
---|
21 | ! |
---|
22 | ! Revision 1.15 2005/05/18 15:44:44 raasch |
---|
23 | ! Extensions for NetCDF output |
---|
24 | ! |
---|
25 | ! Revision 1.14 2001/03/30 07:44:12 raasch |
---|
26 | ! Translation of remaining German identifiers (variables, subroutines, etc.) |
---|
27 | ! |
---|
28 | ! Revision 1.13 2001/03/02 14:21:17 letzel |
---|
29 | ! All comments translated into English. |
---|
30 | ! |
---|
31 | ! Revision 1.12 2001/01/22 07:36:55 raasch |
---|
32 | ! Module test_variables removed |
---|
33 | ! |
---|
34 | ! Revision 1.11 1998/07/06 12:25:36 raasch |
---|
35 | ! + USE test_variables |
---|
36 | ! |
---|
37 | ! Revision 1.10 1998/04/15 11:22:02 raasch |
---|
38 | ! zeitlich gemittelte Profile werden jetzt auch mit zeitlich gemittelten |
---|
39 | ! Groessen normiert |
---|
40 | ! |
---|
41 | ! Revision 1.9 1998/04/06 14:33:53 raasch |
---|
42 | ! Implementierung weiterer Normierungsmethoden |
---|
43 | ! |
---|
44 | ! Revision 1.8 1998/03/30 11:37:30 raasch |
---|
45 | ! Erweiterungen fuer Gebietsstatistiken korrigiert |
---|
46 | ! |
---|
47 | ! Revision 1.7 1998/03/25 13:55:45 raasch |
---|
48 | ! Erweiterungen fuer Gebietsstatistiken |
---|
49 | ! |
---|
50 | ! Revision 1.6 1998/03/09 16:24:04 raasch |
---|
51 | ! Ueberpruefung der Normierungsfaktoren auf 0.0 und evtl. |
---|
52 | ! Abschaltung der Normalisierung |
---|
53 | ! |
---|
54 | ! Revision 1.5 1998/03/03 07:58:11 raasch |
---|
55 | ! Aufruf von flow_statistics erfolgt jetzt gegebenenfalls hier |
---|
56 | ! Ausgabe von zeitlich gemittelten Profilen, Abspeichern von Normierungsgroessen |
---|
57 | ! |
---|
58 | ! Revision 1.4 1998/02/19 07:10:04 raasch |
---|
59 | ! x-Wertebereichsermittelung nur bezueglich des auszugebenden Hoehenbereiches, |
---|
60 | ! x-Wertebereichsermittelung auch fuer Anfangsprofile |
---|
61 | ! |
---|
62 | ! Revision 1.3 1998/02/04 16:09:11 raasch |
---|
63 | ! x-Wertebereiche fuer die einzelnen Koordinatenkreuze ermitteln |
---|
64 | ! |
---|
65 | ! Revision 1.2 1997/09/16 06:38:20 raasch |
---|
66 | ! style- und color-Indexberechnung korrigiert |
---|
67 | ! |
---|
68 | ! Revision 1.1 1997/09/12 06:28:48 raasch |
---|
69 | ! Initial revision |
---|
70 | ! |
---|
71 | ! |
---|
72 | ! Description: |
---|
73 | ! ------------ |
---|
74 | ! Plot output of 1D-profiles for PROFIL |
---|
75 | !------------------------------------------------------------------------------! |
---|
76 | |
---|
77 | USE control_parameters |
---|
78 | USE cpulog |
---|
79 | USE indices |
---|
80 | USE interfaces |
---|
81 | USE netcdf_control |
---|
82 | USE pegrid |
---|
83 | USE profil_parameter |
---|
84 | USE statistics |
---|
85 | |
---|
86 | IMPLICIT NONE |
---|
87 | |
---|
88 | |
---|
89 | INTEGER :: i, id, ilc, ils, j, k, sr |
---|
90 | REAL :: uxma, uxmi |
---|
91 | |
---|
92 | |
---|
93 | ! |
---|
94 | !-- If required, compute statistics |
---|
95 | IF ( .NOT. flow_statistics_called ) CALL flow_statistics |
---|
96 | |
---|
97 | ! |
---|
98 | !-- Flow_statistics has its own CPU time measurement |
---|
99 | CALL cpu_log( log_point(15), 'data_output_profiles', 'start' ) |
---|
100 | |
---|
101 | ! |
---|
102 | !-- If required, compute temporal average |
---|
103 | IF ( averaging_interval_pr == 0.0 ) THEN |
---|
104 | hom_sum(:,:,:) = hom(:,1,:,:) |
---|
105 | ELSE |
---|
106 | IF ( average_count_pr > 0 ) THEN |
---|
107 | hom_sum = hom_sum / REAL( average_count_pr ) |
---|
108 | ELSE |
---|
109 | ! |
---|
110 | !-- This case may happen if dt_dopr is changed in the d3par-list of |
---|
111 | !-- a restart run |
---|
112 | RETURN |
---|
113 | ENDIF |
---|
114 | ENDIF |
---|
115 | |
---|
116 | |
---|
117 | IF ( myid == 0 ) THEN |
---|
118 | |
---|
119 | ! |
---|
120 | !-- Plot-output for each (sub-)region |
---|
121 | |
---|
122 | ! |
---|
123 | !-- Open file for profile output in NetCDF format |
---|
124 | IF ( netcdf_output ) THEN |
---|
125 | CALL check_open( 104 ) |
---|
126 | ENDIF |
---|
127 | |
---|
128 | ! |
---|
129 | !-- Open PROFIL-output files for each (sub-)region |
---|
130 | IF ( profil_output ) THEN |
---|
131 | DO sr = 0, statistic_regions |
---|
132 | CALL check_open( 40 + sr ) |
---|
133 | ENDDO |
---|
134 | ENDIF |
---|
135 | |
---|
136 | ! |
---|
137 | !-- Increment the counter for number of output times |
---|
138 | dopr_time_count = dopr_time_count + 1 |
---|
139 | |
---|
140 | ! |
---|
141 | !-- Re-set to zero the counter for the number of profiles already written |
---|
142 | !-- at the current output time into the respective crosses |
---|
143 | cross_pnc_local = 0 |
---|
144 | |
---|
145 | ! |
---|
146 | !-- Output of initial profiles |
---|
147 | IF ( dopr_time_count == 1 ) THEN |
---|
148 | |
---|
149 | IF ( netcdf_output ) THEN |
---|
150 | #if defined( __netcdf ) |
---|
151 | ! |
---|
152 | !-- Store initial time (t=0) to time axis |
---|
153 | nc_stat = NF90_PUT_VAR( id_set_pr, id_var_time_pr, (/ 0.0 /), & |
---|
154 | start = (/ 1 /), count = (/ 1 /) ) |
---|
155 | IF ( nc_stat /= NF90_NOERR ) CALL handle_netcdf_error( 329 ) |
---|
156 | |
---|
157 | ! |
---|
158 | !-- Store normalization factors |
---|
159 | nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(1), & ! wpt0 |
---|
160 | (/ hom_sum(nzb,18,normalizing_region) /), & |
---|
161 | start = (/ 1 /), count = (/ 1 /) ) |
---|
162 | IF ( nc_stat /= NF90_NOERR ) CALL handle_netcdf_error( 330 ) |
---|
163 | |
---|
164 | nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(2), & ! ws2 |
---|
165 | (/ hom_sum(nzb+8,var_hom,normalizing_region)**2 /), & |
---|
166 | start = (/ 1 /), count = (/ 1 /) ) |
---|
167 | IF ( nc_stat /= NF90_NOERR ) CALL handle_netcdf_error( 331 ) |
---|
168 | |
---|
169 | nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(3), & ! tsw2 |
---|
170 | (/ hom_sum(nzb+3,var_hom,normalizing_region)**2 /), & |
---|
171 | start = (/ 1 /), count = (/ 1 /) ) |
---|
172 | IF ( nc_stat /= NF90_NOERR ) CALL handle_netcdf_error( 332 ) |
---|
173 | |
---|
174 | nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(4), & ! ws3 |
---|
175 | (/ hom_sum(nzb+8,var_hom,normalizing_region)**3 /), & |
---|
176 | start = (/ 1 /), count = (/ 1 /) ) |
---|
177 | IF ( nc_stat /= NF90_NOERR ) CALL handle_netcdf_error( 333 ) |
---|
178 | |
---|
179 | nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(5), & ! ws2tsw |
---|
180 | (/ hom_sum(nzb+8,var_hom,normalizing_region)**3 * & |
---|
181 | hom_sum(nzb+3,var_hom,normalizing_region) /), & |
---|
182 | start = (/ 1 /), count = (/ 1 /) ) |
---|
183 | IF ( nc_stat /= NF90_NOERR ) CALL handle_netcdf_error( 334 ) |
---|
184 | |
---|
185 | nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(6), & ! wstsw2 |
---|
186 | (/ hom_sum(nzb+8,var_hom,normalizing_region) * & |
---|
187 | hom_sum(nzb+3,var_hom,normalizing_region)**2 /), & |
---|
188 | start = (/ 1 /), count = (/ 1 /) ) |
---|
189 | IF ( nc_stat /= NF90_NOERR ) CALL handle_netcdf_error( 335 ) |
---|
190 | |
---|
191 | nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(7), & ! z_i |
---|
192 | (/ hom_sum(nzb+6,var_hom,normalizing_region) /), & |
---|
193 | start = (/ 1 /), count = (/ 1 /) ) |
---|
194 | IF ( nc_stat /= NF90_NOERR ) CALL handle_netcdf_error( 336 ) |
---|
195 | #endif |
---|
196 | ENDIF |
---|
197 | ! |
---|
198 | !-- Loop over all 1D variables |
---|
199 | DO i = 1, dopr_n |
---|
200 | |
---|
201 | IF ( dopr_initial_index(i) /= 0 ) THEN |
---|
202 | |
---|
203 | ! |
---|
204 | !-- Output for the individual (sub-)regions |
---|
205 | DO sr = 0, statistic_regions |
---|
206 | |
---|
207 | IF ( profil_output ) THEN |
---|
208 | id = 40 + sr |
---|
209 | ! |
---|
210 | !-- Write Label-Header |
---|
211 | WRITE ( id, 100 ) TRIM( data_output_pr(i) ), '(t=0)' |
---|
212 | ! |
---|
213 | !-- Write total profile |
---|
214 | DO k = nzb, nzt+1 |
---|
215 | WRITE ( id, 101 ) hom(k,2,dopr_initial_index(i),sr), & |
---|
216 | hom(k,1,dopr_initial_index(i),sr) |
---|
217 | ENDDO |
---|
218 | ! |
---|
219 | !-- Write separation label |
---|
220 | WRITE ( id, 102 ) |
---|
221 | ENDIF |
---|
222 | |
---|
223 | IF ( netcdf_output ) THEN |
---|
224 | #if defined( __netcdf ) |
---|
225 | ! |
---|
226 | !-- Write data to netcdf file |
---|
227 | nc_stat = NF90_PUT_VAR( id_set_pr, id_var_dopr(i,sr), & |
---|
228 | hom(nzb:nzt+1,1,dopr_initial_index(i),sr), & |
---|
229 | start = (/ 1, 1 /), & |
---|
230 | count = (/ nzt-nzb+2, 1 /) ) |
---|
231 | IF ( nc_stat /= NF90_NOERR ) & |
---|
232 | CALL handle_netcdf_error( 337 ) |
---|
233 | #endif |
---|
234 | ENDIF |
---|
235 | |
---|
236 | ENDDO |
---|
237 | |
---|
238 | IF ( profil_output ) THEN |
---|
239 | ! |
---|
240 | !-- Determine indices for later NAMELIST-output (s. below) |
---|
241 | profile_number = profile_number + 1 |
---|
242 | j = dopr_crossindex(i) |
---|
243 | IF ( j /= 0 ) THEN |
---|
244 | cross_profile_number_count(j) = & |
---|
245 | cross_profile_number_count(j) + 1 |
---|
246 | k = cross_profile_number_count(j) |
---|
247 | cross_profile_numbers(k,j) = profile_number |
---|
248 | ! |
---|
249 | !-- Initial profiles are always drawn as solid lines in |
---|
250 | !-- anti-background colour. |
---|
251 | cross_linecolors(k,j) = 1 |
---|
252 | cross_linestyles(k,j) = 0 |
---|
253 | ! |
---|
254 | !-- If required, extend x-value range of the respective |
---|
255 | !-- cross, provided it has not been specified in & |
---|
256 | !-- check_parameters. Determination over all (sub-)regions. |
---|
257 | IF ( cross_uxmin(j) == 0.0 .AND. & |
---|
258 | cross_uxmax(j) == 0.0 ) THEN |
---|
259 | |
---|
260 | DO sr = 0, statistic_regions |
---|
261 | |
---|
262 | uxmi = & |
---|
263 | MINVAL( hom(:nz_do1d,1,dopr_initial_index(i),sr) ) |
---|
264 | |
---|
265 | uxma = & |
---|
266 | MAXVAL( hom(:nz_do1d,1,dopr_initial_index(i),sr) ) |
---|
267 | ! |
---|
268 | !-- When the value range of the first line in the |
---|
269 | !-- corresponding cross is determined, its value range |
---|
270 | !-- is simply adopted. |
---|
271 | IF ( cross_uxmin_computed(j) > & |
---|
272 | cross_uxmax_computed(j) ) THEN |
---|
273 | cross_uxmin_computed(j) = uxmi |
---|
274 | cross_uxmax_computed(j) = uxma |
---|
275 | ELSE |
---|
276 | cross_uxmin_computed(j) = & |
---|
277 | MIN( cross_uxmin_computed(j), uxmi ) |
---|
278 | cross_uxmax_computed(j) = & |
---|
279 | MAX( cross_uxmax_computed(j), uxma ) |
---|
280 | ENDIF |
---|
281 | |
---|
282 | ENDDO |
---|
283 | |
---|
284 | ENDIF |
---|
285 | ! |
---|
286 | !-- If required, determine and note normalizing factors |
---|
287 | SELECT CASE ( cross_normalized_x(j) ) |
---|
288 | |
---|
289 | CASE ( 'ts2' ) |
---|
290 | cross_normx_factor(k,j) = & |
---|
291 | ( hom_sum(nzb+3,var_hom,normalizing_region) )**2 |
---|
292 | CASE ( 'wpt0' ) |
---|
293 | cross_normx_factor(k,j) = & |
---|
294 | hom_sum(nzb,18,normalizing_region) |
---|
295 | CASE ( 'wsts2' ) |
---|
296 | cross_normx_factor(k,j) = & |
---|
297 | hom_sum(nzb+8,var_hom,normalizing_region) & |
---|
298 | * ( hom_sum(nzb+3,var_hom,normalizing_region) )**2 |
---|
299 | CASE ( 'ws2' ) |
---|
300 | cross_normx_factor(k,j) = & |
---|
301 | ( hom_sum(nzb+8,var_hom,normalizing_region) )**2 |
---|
302 | CASE ( 'ws2ts' ) |
---|
303 | cross_normx_factor(k,j) = & |
---|
304 | ( hom_sum(nzb+8,var_hom,normalizing_region) )**2 & |
---|
305 | * hom_sum(nzb+3,var_hom,normalizing_region) |
---|
306 | CASE ( 'ws3' ) |
---|
307 | cross_normx_factor(k,j) = & |
---|
308 | ( hom_sum(nzb+8,var_hom,normalizing_region) )**3 |
---|
309 | |
---|
310 | END SELECT |
---|
311 | |
---|
312 | SELECT CASE ( cross_normalized_y(j) ) |
---|
313 | |
---|
314 | CASE ( 'z_i' ) |
---|
315 | cross_normy_factor(k,j) = & |
---|
316 | hom_sum(nzb+6,var_hom,normalizing_region) |
---|
317 | |
---|
318 | END SELECT |
---|
319 | |
---|
320 | ! |
---|
321 | !-- Check the normalizing factors for zeros and deactivate |
---|
322 | !-- the normalization, if required. |
---|
323 | IF ( cross_normx_factor(k,j) == 0.0 .OR. & |
---|
324 | cross_normy_factor(k,j) == 0.0 ) THEN |
---|
325 | PRINT*,'+++ WARNING data_output_profiles: normalizi', & |
---|
326 | 'ng cross ',j, ' is not possible since one o', & |
---|
327 | 'f the' |
---|
328 | PRINT*,' normalizing factors is ',& |
---|
329 | 'zero!' |
---|
330 | PRINT*,' cross_normx_factor(',k,',',j,') = ', & |
---|
331 | cross_normx_factor(k,j) |
---|
332 | PRINT*,' cross_normy_factor(',k,',',j,') = ', & |
---|
333 | cross_normy_factor(k,j) |
---|
334 | cross_normx_factor(k,j) = 1.0 |
---|
335 | cross_normy_factor(k,j) = 1.0 |
---|
336 | cross_normalized_x(j) = ' ' |
---|
337 | cross_normalized_y(j) = ' ' |
---|
338 | ENDIF |
---|
339 | |
---|
340 | ! |
---|
341 | !-- If required, extend normalized x-value range of the |
---|
342 | !-- respective cross, provided it has not been specified in |
---|
343 | !-- check_parameters. Determination over all (sub-)regions. |
---|
344 | IF ( cross_uxmin_normalized(j) == 0.0 .AND. & |
---|
345 | cross_uxmax_normalized(j) == 0.0 ) THEN |
---|
346 | |
---|
347 | DO sr = 0, statistic_regions |
---|
348 | |
---|
349 | uxmi = MINVAL( hom(:nz_do1d,1, & |
---|
350 | dopr_initial_index(i),sr) ) / & |
---|
351 | cross_normx_factor(k,j) |
---|
352 | uxma = MAXVAL( hom(:nz_do1d,1, & |
---|
353 | dopr_initial_index(i),sr) ) / & |
---|
354 | cross_normx_factor(k,j) |
---|
355 | ! |
---|
356 | !-- When the value range of the first line in the |
---|
357 | !-- corresponding cross is determined, its value range |
---|
358 | !-- is simply adopted. |
---|
359 | IF ( cross_uxmin_normalized_computed(j) > & |
---|
360 | cross_uxmax_normalized_computed(j) ) THEN |
---|
361 | cross_uxmin_normalized_computed(j) = uxmi |
---|
362 | cross_uxmax_normalized_computed(j) = uxma |
---|
363 | ELSE |
---|
364 | cross_uxmin_normalized_computed(j) = & |
---|
365 | MIN( cross_uxmin_normalized_computed(j), uxmi ) |
---|
366 | cross_uxmax_normalized_computed(j) = & |
---|
367 | MAX( cross_uxmax_normalized_computed(j), uxma ) |
---|
368 | ENDIF |
---|
369 | |
---|
370 | ENDDO |
---|
371 | |
---|
372 | ENDIF |
---|
373 | |
---|
374 | ENDIF ! Index determination |
---|
375 | |
---|
376 | ENDIF ! profil output |
---|
377 | |
---|
378 | ENDIF ! Initial profile available |
---|
379 | |
---|
380 | ENDDO ! Loop over dopr_n for initial profiles |
---|
381 | |
---|
382 | IF ( netcdf_output ) dopr_time_count = dopr_time_count + 1 |
---|
383 | |
---|
384 | ENDIF ! Initial profiles |
---|
385 | |
---|
386 | IF ( netcdf_output ) THEN |
---|
387 | #if defined( __netcdf ) |
---|
388 | ! |
---|
389 | !-- Store time to time axis |
---|
390 | nc_stat = NF90_PUT_VAR( id_set_pr, id_var_time_pr, & |
---|
391 | (/ simulated_time /), & |
---|
392 | start = (/ dopr_time_count /), & |
---|
393 | count = (/ 1 /) ) |
---|
394 | IF ( nc_stat /= NF90_NOERR ) CALL handle_netcdf_error( 338 ) |
---|
395 | |
---|
396 | ! |
---|
397 | !-- Store normalization factors |
---|
398 | nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(1), & ! wpt0 |
---|
399 | (/ hom_sum(nzb,18,normalizing_region) /), & |
---|
400 | start = (/ dopr_time_count /), & |
---|
401 | count = (/ 1 /) ) |
---|
402 | IF ( nc_stat /= NF90_NOERR ) CALL handle_netcdf_error( 339 ) |
---|
403 | |
---|
404 | nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(2), & ! ws2 |
---|
405 | (/ hom_sum(nzb+8,var_hom,normalizing_region)**2 /), & |
---|
406 | start = (/ dopr_time_count /), & |
---|
407 | count = (/ 1 /) ) |
---|
408 | IF ( nc_stat /= NF90_NOERR ) CALL handle_netcdf_error( 340 ) |
---|
409 | |
---|
410 | nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(3), & ! tsw2 |
---|
411 | (/ hom_sum(nzb+3,var_hom,normalizing_region)**2 /), & |
---|
412 | start = (/ dopr_time_count /), & |
---|
413 | count = (/ 1 /) ) |
---|
414 | IF ( nc_stat /= NF90_NOERR ) CALL handle_netcdf_error( 341 ) |
---|
415 | |
---|
416 | nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(4), & ! ws3 |
---|
417 | (/ hom_sum(nzb+8,var_hom,normalizing_region)**3 /), & |
---|
418 | start = (/ dopr_time_count /), & |
---|
419 | count = (/ 1 /) ) |
---|
420 | IF ( nc_stat /= NF90_NOERR ) CALL handle_netcdf_error( 342 ) |
---|
421 | |
---|
422 | nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(5), & ! ws2tsw |
---|
423 | (/ hom_sum(nzb+8,var_hom,normalizing_region)**3 * & |
---|
424 | hom_sum(nzb+3,var_hom,normalizing_region) /), & |
---|
425 | start = (/ dopr_time_count /), & |
---|
426 | count = (/ 1 /) ) |
---|
427 | IF ( nc_stat /= NF90_NOERR ) CALL handle_netcdf_error( 343 ) |
---|
428 | |
---|
429 | nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(6), & ! wstsw2 |
---|
430 | (/ hom_sum(nzb+8,var_hom,normalizing_region) * & |
---|
431 | hom_sum(nzb+3,var_hom,normalizing_region)**2 /), & |
---|
432 | start = (/ dopr_time_count /), & |
---|
433 | count = (/ 1 /) ) |
---|
434 | IF ( nc_stat /= NF90_NOERR ) CALL handle_netcdf_error( 344 ) |
---|
435 | |
---|
436 | nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(7), & ! z_i |
---|
437 | (/ hom_sum(nzb+6,var_hom,normalizing_region) /), & |
---|
438 | start = (/ dopr_time_count /), & |
---|
439 | count = (/ 1 /) ) |
---|
440 | IF ( nc_stat /= NF90_NOERR ) CALL handle_netcdf_error( 345 ) |
---|
441 | #endif |
---|
442 | ENDIF |
---|
443 | |
---|
444 | ! |
---|
445 | !-- Output of the individual (non-initial) profiles |
---|
446 | DO i = 1, dopr_n |
---|
447 | |
---|
448 | ! |
---|
449 | !-- Output for the individual (sub-)domains |
---|
450 | DO sr = 0, statistic_regions |
---|
451 | |
---|
452 | IF ( profil_output ) THEN |
---|
453 | id = 40 + sr |
---|
454 | ! |
---|
455 | !-- Write Label-Header |
---|
456 | WRITE ( id, 100 ) TRIM( dopr_label(i) ), simulated_time_chr |
---|
457 | ! |
---|
458 | !-- Output of total profile |
---|
459 | DO k = nzb, nzt+1 |
---|
460 | WRITE ( id, 101 ) hom(k,2,dopr_index(i),sr), & |
---|
461 | hom_sum(k,dopr_index(i),sr) |
---|
462 | ENDDO |
---|
463 | ! |
---|
464 | !-- Write separation label |
---|
465 | WRITE ( id, 102 ) |
---|
466 | ENDIF |
---|
467 | |
---|
468 | IF ( netcdf_output ) THEN |
---|
469 | #if defined( __netcdf ) |
---|
470 | ! |
---|
471 | !-- Write data to netcdf file |
---|
472 | nc_stat = NF90_PUT_VAR( id_set_pr, id_var_dopr(i,sr), & |
---|
473 | hom_sum(nzb:nzt+1,dopr_index(i),sr),& |
---|
474 | start = (/ 1, dopr_time_count /), & |
---|
475 | count = (/ nzt-nzb+2, 1 /) ) |
---|
476 | IF ( nc_stat /= NF90_NOERR ) CALL handle_netcdf_error( 346 ) |
---|
477 | #endif |
---|
478 | ENDIF |
---|
479 | |
---|
480 | ENDDO |
---|
481 | |
---|
482 | IF ( profil_output ) THEN |
---|
483 | ! |
---|
484 | !-- Determine profile number on file and note the data for later |
---|
485 | !-- NAMELIST output, if the respective profile is to be drawn by |
---|
486 | !-- PROFIL (if it shall not be drawn, the variable dopr_crossindex has |
---|
487 | !-- the value 0, otherwise the number of the coordinate cross) |
---|
488 | profile_number = profile_number + 1 |
---|
489 | j = dopr_crossindex(i) |
---|
490 | |
---|
491 | IF ( j /= 0 ) THEN |
---|
492 | cross_profile_number_count(j) = cross_profile_number_count(j) +1 |
---|
493 | k = cross_profile_number_count(j) |
---|
494 | cross_pnc_local(j) = cross_pnc_local(j) +1 |
---|
495 | cross_profile_numbers(k,j) = profile_number |
---|
496 | ilc = MOD( dopr_time_count, 10 ) |
---|
497 | IF ( ilc == 0 ) ilc = 10 |
---|
498 | cross_linecolors(k,j) = linecolors(ilc) |
---|
499 | ils = MOD( cross_pnc_local(j), 11 ) |
---|
500 | IF ( ils == 0 ) ils = 11 |
---|
501 | cross_linestyles(k,j) = linestyles(ils) |
---|
502 | ! |
---|
503 | !-- If required, extend x-value range of the respective coordinate |
---|
504 | !-- cross, provided it has not been specified in check_parameters. |
---|
505 | !-- Determination over all (sub-)regions. |
---|
506 | IF ( cross_uxmin(j) == 0.0 .AND. cross_uxmax(j) == 0.0 ) THEN |
---|
507 | |
---|
508 | DO sr = 0, statistic_regions |
---|
509 | |
---|
510 | uxmi = MINVAL( hom_sum(:nz_do1d,dopr_index(i),sr) ) |
---|
511 | uxma = MAXVAL( hom_sum(:nz_do1d,dopr_index(i),sr) ) |
---|
512 | ! |
---|
513 | !-- When the value range of the first line in the |
---|
514 | !-- corresponding cross is determined, its value range is |
---|
515 | !-- simply adopted. |
---|
516 | IF ( cross_uxmin_computed(j) > cross_uxmax_computed(j) ) & |
---|
517 | THEN |
---|
518 | cross_uxmin_computed(j) = uxmi |
---|
519 | cross_uxmax_computed(j) = uxma |
---|
520 | ELSE |
---|
521 | cross_uxmin_computed(j) = & |
---|
522 | MIN( cross_uxmin_computed(j), uxmi ) |
---|
523 | cross_uxmax_computed(j) = & |
---|
524 | MAX( cross_uxmax_computed(j), uxma ) |
---|
525 | ENDIF |
---|
526 | |
---|
527 | ENDDO |
---|
528 | |
---|
529 | ENDIF |
---|
530 | ! |
---|
531 | !-- If required, store the normalizing factors |
---|
532 | SELECT CASE ( cross_normalized_x(j) ) |
---|
533 | |
---|
534 | CASE ( 'tsw2' ) |
---|
535 | cross_normx_factor(k,j) = & |
---|
536 | ( hom_sum(nzb+11,var_hom,normalizing_region) )**2 |
---|
537 | CASE ( 'wpt0' ) |
---|
538 | cross_normx_factor(k,j) = & |
---|
539 | hom_sum(nzb,18,normalizing_region) |
---|
540 | CASE ( 'wstsw2' ) |
---|
541 | cross_normx_factor(k,j) = & |
---|
542 | hom_sum(nzb+8,var_hom,normalizing_region) & |
---|
543 | * ( hom_sum(nzb+11,var_hom,normalizing_region) )**2 |
---|
544 | CASE ( 'ws2' ) |
---|
545 | cross_normx_factor(k,j) = & |
---|
546 | ( hom_sum(nzb+8,var_hom,normalizing_region) )**2 |
---|
547 | CASE ( 'ws2tsw' ) |
---|
548 | cross_normx_factor(k,j) = & |
---|
549 | ( hom_sum(nzb+8,var_hom,normalizing_region) )**2& |
---|
550 | * hom_sum(nzb+11,var_hom,normalizing_region) |
---|
551 | CASE ( 'ws3' ) |
---|
552 | cross_normx_factor(k,j) = & |
---|
553 | ( hom_sum(nzb+8,var_hom,normalizing_region) )**3 |
---|
554 | |
---|
555 | END SELECT |
---|
556 | SELECT CASE ( cross_normalized_y(j) ) |
---|
557 | |
---|
558 | CASE ( 'z_i' ) |
---|
559 | cross_normy_factor(k,j) = & |
---|
560 | hom_sum(nzb+6,var_hom,normalizing_region) |
---|
561 | |
---|
562 | END SELECT |
---|
563 | |
---|
564 | ! |
---|
565 | !-- Check the normalizing factors for zeros and deactivate the |
---|
566 | !-- normalization, if required. |
---|
567 | IF ( cross_normx_factor(k,j) == 0.0 .OR. & |
---|
568 | cross_normy_factor(k,j) == 0.0 ) THEN |
---|
569 | PRINT*,'+++ WARNING data_output_profiles: normalizing ',j, & |
---|
570 | ' cross is not possible since one of the' |
---|
571 | PRINT*,' normalizing factors is zero!' |
---|
572 | PRINT*,' cross_normx_factor(',k,',',j,') = ', & |
---|
573 | cross_normx_factor(k,j) |
---|
574 | PRINT*,' cross_normy_factor(',k,',',j,') = ', & |
---|
575 | cross_normy_factor(k,j) |
---|
576 | cross_normx_factor(k,j) = 1.0 |
---|
577 | cross_normy_factor(k,j) = 1.0 |
---|
578 | cross_normalized_x(j) = ' ' |
---|
579 | cross_normalized_y(j) = ' ' |
---|
580 | ENDIF |
---|
581 | |
---|
582 | ! |
---|
583 | !-- If required, extend normalized x-value range of the respective |
---|
584 | !-- cross, provided it has not been specified in check_parameters. |
---|
585 | !-- Determination over all (sub-)regions. |
---|
586 | IF ( cross_uxmin_normalized(j) == 0.0 .AND. & |
---|
587 | cross_uxmax_normalized(j) == 0.0 ) THEN |
---|
588 | |
---|
589 | DO sr = 0, statistic_regions |
---|
590 | |
---|
591 | uxmi = MINVAL( hom(:nz_do1d,1,dopr_index(i),sr) ) / & |
---|
592 | cross_normx_factor(k,j) |
---|
593 | uxma = MAXVAL( hom(:nz_do1d,1,dopr_index(i),sr) ) / & |
---|
594 | cross_normx_factor(k,j) |
---|
595 | ! |
---|
596 | !-- When the value range of the first line in the |
---|
597 | !-- corresponding cross is determined, its value range is |
---|
598 | !-- simply adopted. |
---|
599 | IF ( cross_uxmin_normalized_computed(j) > & |
---|
600 | cross_uxmax_normalized_computed(j) ) THEN |
---|
601 | cross_uxmin_normalized_computed(j) = uxmi |
---|
602 | cross_uxmax_normalized_computed(j) = uxma |
---|
603 | ELSE |
---|
604 | cross_uxmin_normalized_computed(j) = & |
---|
605 | MIN( cross_uxmin_normalized_computed(j), uxmi ) |
---|
606 | cross_uxmax_normalized_computed(j) = & |
---|
607 | MAX( cross_uxmax_normalized_computed(j), uxma ) |
---|
608 | ENDIF |
---|
609 | |
---|
610 | ENDDO |
---|
611 | |
---|
612 | ENDIF |
---|
613 | |
---|
614 | ENDIF ! Index determination |
---|
615 | |
---|
616 | ENDIF ! profil output |
---|
617 | |
---|
618 | ENDDO ! Loop over dopr_n |
---|
619 | |
---|
620 | ENDIF ! Output on PE0 |
---|
621 | |
---|
622 | ! |
---|
623 | !-- If averaging has been done above, the summation counter must be re-set. |
---|
624 | IF ( averaging_interval_pr /= 0.0 ) THEN |
---|
625 | average_count_pr = 0 |
---|
626 | ENDIF |
---|
627 | |
---|
628 | CALL cpu_log( log_point(15), 'data_output_profiles','stop', 'nobarrier' ) |
---|
629 | |
---|
630 | ! |
---|
631 | !-- Formats |
---|
632 | 100 FORMAT ('#1 ',A,1X,A) |
---|
633 | 101 FORMAT (E15.7,1X,E15.7) |
---|
634 | 102 FORMAT ('NEXT') |
---|
635 | |
---|
636 | END SUBROUTINE data_output_profiles |
---|