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

Last change on this file since 197 was 197, checked in by raasch, 16 years ago

further adjustments for SGI and other small changes

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