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

Last change on this file since 256 was 254, checked in by heinze, 15 years ago

Output of messages replaced by message handling routine.

  • Property svn:keywords set to Id
File size: 25.0 KB
Line 
1 SUBROUTINE data_output_profiles
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6! Output of messages replaced by message handling routine.
7!
8!
9! Former revisions:
10! -----------------
11! $Id: data_output_profiles.f90 254 2009-03-05 15:33:42Z letzel $
12!
13! 197 2008-09-16 15:29:03Z raasch
14! Time coordinate t=0 stored on netcdf-file only if an output is required for
15! this time for at least one of the profiles
16!
17! February 2007
18! RCS Log replace by Id keyword, revision history cleaned up
19!
20! 87 2007-05-22 15:46:47Z raasch
21! var_hom renamed pr_palm
22!
23! Revision 1.18  2006/08/16 14:27:04  raasch
24! PRINT* statements for testing removed
25!
26! Revision 1.1  1997/09/12 06:28:48  raasch
27! Initial revision
28!
29!
30! Description:
31! ------------
32! Plot output of 1D-profiles for PROFIL
33!------------------------------------------------------------------------------!
34
35    USE control_parameters
36    USE cpulog
37    USE indices
38    USE interfaces
39    USE netcdf_control
40    USE pegrid
41    USE profil_parameter
42    USE statistics
43
44    IMPLICIT NONE
45
46
47    INTEGER ::  i, id, ilc, ils, j, k, sr
48    LOGICAL ::  output_for_t0
49    REAL    ::  uxma, uxmi
50
51
52!
53!-- If required, compute statistics
54    IF ( .NOT. flow_statistics_called )  CALL flow_statistics
55
56!
57!-- Flow_statistics has its own CPU time measurement
58    CALL cpu_log( log_point(15), 'data_output_profiles', 'start' )
59
60!
61!-- If required, compute temporal average
62    IF ( averaging_interval_pr == 0.0 )  THEN
63       hom_sum(:,:,:) = hom(:,1,:,:)
64    ELSE
65       IF ( average_count_pr > 0 )  THEN
66          hom_sum = hom_sum / REAL( average_count_pr )
67       ELSE
68!
69!--       This case may happen if dt_dopr is changed in the d3par-list of
70!--       a restart run
71          RETURN
72       ENDIF
73    ENDIF
74
75   
76    IF ( myid == 0 )  THEN
77
78!
79!--    Plot-output for each (sub-)region
80
81!
82!--    Open file for profile output in NetCDF format
83       IF ( netcdf_output )  THEN
84          CALL check_open( 104 )
85       ENDIF
86
87!
88!--    Open PROFIL-output files for each (sub-)region
89       IF ( profil_output )  THEN
90          DO  sr = 0, statistic_regions
91             CALL check_open( 40 + sr )
92          ENDDO
93       ENDIF
94
95!
96!--    Increment the counter for number of output times
97       dopr_time_count = dopr_time_count + 1
98
99!
100!--    Re-set to zero the counter for the number of profiles already written
101!--    at the current output time into the respective crosses
102       cross_pnc_local = 0
103
104!
105!--    Output of initial profiles
106       IF ( dopr_time_count == 1 )  THEN
107
108          IF ( netcdf_output )  THEN
109#if defined( __netcdf )
110!
111!--          Store initial time (t=0) to time axis, but only if an output
112!--          is required for at least one of the profiles
113             output_for_t0 = .FALSE.
114             DO  i = 1, dopr_n
115                IF ( dopr_initial_index(i) /= 0 )  THEN
116                   nc_stat = NF90_PUT_VAR( id_set_pr, id_var_time_pr,  &
117                                           (/ 0.0 /), start = (/ 1 /), &
118                                           count = (/ 1 /) )
119                   IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 329 )
120                   output_for_t0 = .TRUE.
121                   EXIT
122                ENDIF
123             ENDDO
124
125!
126!--          Store normalization factors
127             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(1), &  ! wpt0
128                                  (/ hom_sum(nzb,18,normalizing_region) /), &
129                                     start = (/ 1 /), count = (/ 1 /) )
130             IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 330 )
131
132             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(2), &  ! ws2
133                        (/ hom_sum(nzb+8,pr_palm,normalizing_region)**2 /), &
134                                     start = (/ 1 /), count = (/ 1 /) )
135             IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 331 )
136
137             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(3), &  ! tsw2
138                        (/ hom_sum(nzb+3,pr_palm,normalizing_region)**2 /), &
139                                     start = (/ 1 /), count = (/ 1 /) )
140             IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 332 )
141
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             IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 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             IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 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             IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 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             IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 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                      IF ( nc_stat /= NF90_NOERR )  &
200                                                CALL handle_netcdf_error( 337 )
201#endif
202                   ENDIF
203
204                ENDDO
205
206                IF ( profil_output )  THEN
207!
208!--                Determine indices for later NAMELIST-output (s. below)
209                   profile_number = profile_number + 1
210                   j = dopr_crossindex(i)
211                   IF ( j /= 0 )  THEN
212                      cross_profile_number_count(j) = &
213                                               cross_profile_number_count(j) + 1
214                      k = cross_profile_number_count(j)
215                      cross_profile_numbers(k,j) = profile_number
216!
217!--                   Initial profiles are always drawn as solid lines in
218!--                   anti-background colour.
219                      cross_linecolors(k,j) = 1
220                      cross_linestyles(k,j) = 0
221!
222!--                   If required, extend x-value range of the respective
223!--                   cross, provided it has not been specified in &
224!--                   check_parameters. Determination over all (sub-)regions.
225                      IF ( cross_uxmin(j) == 0.0  .AND. &
226                           cross_uxmax(j) == 0.0 )  THEN
227
228                         DO  sr = 0, statistic_regions
229
230                            uxmi = &
231                            MINVAL( hom(:nz_do1d,1,dopr_initial_index(i),sr) )
232
233                            uxma = &
234                            MAXVAL( hom(:nz_do1d,1,dopr_initial_index(i),sr) )
235!
236!--                         When the value range of the first line in the
237!--                         corresponding cross is determined, its value range
238!--                         is simply adopted.
239                            IF ( cross_uxmin_computed(j) > &
240                                 cross_uxmax_computed(j) )  THEN
241                               cross_uxmin_computed(j) = uxmi
242                               cross_uxmax_computed(j) = uxma
243                            ELSE
244                               cross_uxmin_computed(j) = &
245                                            MIN( cross_uxmin_computed(j), uxmi )
246                               cross_uxmax_computed(j) = &
247                                            MAX( cross_uxmax_computed(j), uxma )
248                            ENDIF
249
250                         ENDDO
251
252                      ENDIF
253!
254!--                   If required, determine and note normalizing factors
255                      SELECT CASE ( cross_normalized_x(j) )
256
257                         CASE ( 'ts2' )
258                            cross_normx_factor(k,j) = &
259                             ( hom_sum(nzb+3,pr_palm,normalizing_region) )**2
260                         CASE ( 'wpt0' )
261                            cross_normx_factor(k,j) = &
262                             hom_sum(nzb,18,normalizing_region)
263                         CASE ( 'wsts2' )
264                            cross_normx_factor(k,j) = &
265                             hom_sum(nzb+8,pr_palm,normalizing_region)  &
266                           * ( hom_sum(nzb+3,pr_palm,normalizing_region) )**2
267                         CASE ( 'ws2' )
268                            cross_normx_factor(k,j) = &
269                             ( hom_sum(nzb+8,pr_palm,normalizing_region) )**2
270                         CASE ( 'ws2ts' )
271                            cross_normx_factor(k,j) = &
272                           ( hom_sum(nzb+8,pr_palm,normalizing_region) )**2 &
273                           * hom_sum(nzb+3,pr_palm,normalizing_region)
274                         CASE ( 'ws3' )
275                            cross_normx_factor(k,j) = &
276                             ( hom_sum(nzb+8,pr_palm,normalizing_region) )**3
277
278                      END SELECT
279
280                      SELECT CASE ( cross_normalized_y(j) )
281
282                         CASE ( 'z_i' )
283                            cross_normy_factor(k,j) = &
284                                    hom_sum(nzb+6,pr_palm,normalizing_region)
285
286                      END SELECT
287
288!
289!--                   Check the normalizing factors for zeros and deactivate
290!--                   the normalization, if required.
291                      IF ( cross_normx_factor(k,j) == 0.0  .OR. &
292                           cross_normy_factor(k,j) == 0.0 )  THEN
293                         WRITE( message_string, * ) 'data_output_profiles: normalizi', &
294                                                    'ng cross ',j, ' is not possible since one o', &
295                                                    'f the & normalizing factors is zero! & ', &
296                                                    'cross_normx_factor(',k,',',j,') = ', &
297                                                     cross_normx_factor(k,j), &
298                                                    ' & cross_normy_factor(',k,',',j,') = ', &
299                                                     cross_normy_factor(k,j)
300                         CALL message( 'data_output_profiles', 'PA0185', 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                                  (/ simulated_time /),          &
361                                  start = (/ dopr_time_count /), &
362                                  count = (/ 1 /) )
363          IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 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          IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 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          IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 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          IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 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          IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 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          IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 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          IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 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          IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 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                IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 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: normalizi', &
539                                              'ng cross ',j, ' is not possible since one o', &
540                                              'f the & normalizing factors is zero! & ', &
541                                              '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', 0, 1, 0, 6, 0 )
546                    cross_normx_factor(k,j) = 1.0
547                    cross_normy_factor(k,j) = 1.0
548                    cross_normalized_x(j) = ' '
549                    cross_normalized_y(j) = ' '
550                ENDIF
551
552!
553!--             If required, extend normalized x-value range of the respective 
554!--             cross, provided it has not been specified in check_parameters.
555!--             Determination over all (sub-)regions.
556                IF ( cross_uxmin_normalized(j) == 0.0  .AND. &
557                     cross_uxmax_normalized(j) == 0.0 )  THEN
558
559                   DO  sr = 0, statistic_regions
560
561                      uxmi = MINVAL( hom(:nz_do1d,1,dopr_index(i),sr) ) / &
562                             cross_normx_factor(k,j)
563                      uxma = MAXVAL( hom(:nz_do1d,1,dopr_index(i),sr) ) / &
564                             cross_normx_factor(k,j)
565!
566!--                   When the value range of the first line in the
567!--                   corresponding cross is determined, its value range is
568!--                   simply adopted.
569                      IF ( cross_uxmin_normalized_computed(j) > &
570                           cross_uxmax_normalized_computed(j) )  THEN
571                         cross_uxmin_normalized_computed(j) = uxmi
572                         cross_uxmax_normalized_computed(j) = uxma
573                      ELSE
574                         cross_uxmin_normalized_computed(j) = &
575                                MIN( cross_uxmin_normalized_computed(j), uxmi )
576                         cross_uxmax_normalized_computed(j) = &
577                                MAX( cross_uxmax_normalized_computed(j), uxma )
578                      ENDIF
579
580                   ENDDO
581
582                ENDIF
583
584             ENDIF   ! Index determination
585
586          ENDIF   ! profil output
587
588       ENDDO   ! Loop over dopr_n
589
590    ENDIF  ! Output on PE0
591
592!
593!-- If averaging has been done above, the summation counter must be re-set.
594    IF ( averaging_interval_pr /= 0.0 )  THEN
595       average_count_pr = 0
596    ENDIF
597
598    CALL cpu_log( log_point(15), 'data_output_profiles','stop', 'nobarrier' )
599
600!
601!-- Formats
602100 FORMAT ('#1 ',A,1X,A)
603101 FORMAT (E15.7,1X,E15.7)
604102 FORMAT ('NEXT')
605
606 END SUBROUTINE data_output_profiles
Note: See TracBrowser for help on using the repository browser.