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

Last change on this file since 367 was 345, checked in by heinze, 15 years ago

In case of restart runs without extension, initial profiles are not written to NetCDF-file anymore.

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