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

Last change on this file since 306 was 291, checked in by raasch, 15 years ago

changes for coupling with independent precursor runs; z_i calculation with Sullivan criterion

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