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

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

file headers updated for the next release 3.5

  • Property svn:keywords set to Id
File size: 24.6 KB
RevLine 
[1]1 SUBROUTINE data_output_profiles
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
[198]6!
[1]7!
8! Former revisions:
9! -----------------
[3]10! $Id: data_output_profiles.f90 198 2008-09-17 08:55:28Z raasch $
[198]11!
12! 197 2008-09-16 15:29:03Z raasch
13! Time coordinate t=0 stored on netcdf-file only if an output is required for
14! this time for at least one of the profiles
15!
16! February 2007
[3]17! RCS Log replace by Id keyword, revision history cleaned up
18!
[90]19! 87 2007-05-22 15:46:47Z raasch
20! var_hom renamed pr_palm
21!
[1]22! Revision 1.18  2006/08/16 14:27:04  raasch
23! PRINT* statements for testing removed
24!
25! Revision 1.1  1997/09/12 06:28:48  raasch
26! Initial revision
27!
28!
29! Description:
30! ------------
31! Plot output of 1D-profiles for PROFIL
32!------------------------------------------------------------------------------!
33
34    USE control_parameters
35    USE cpulog
36    USE indices
37    USE interfaces
38    USE netcdf_control
39    USE pegrid
40    USE profil_parameter
41    USE statistics
42
43    IMPLICIT NONE
44
45
46    INTEGER ::  i, id, ilc, ils, j, k, sr
[197]47    LOGICAL ::  output_for_t0
[1]48    REAL    ::  uxma, uxmi
49
50
51!
52!-- If required, compute statistics
53    IF ( .NOT. flow_statistics_called )  CALL flow_statistics
54
55!
56!-- Flow_statistics has its own CPU time measurement
57    CALL cpu_log( log_point(15), 'data_output_profiles', 'start' )
58
59!
60!-- If required, compute temporal average
61    IF ( averaging_interval_pr == 0.0 )  THEN
62       hom_sum(:,:,:) = hom(:,1,:,:)
63    ELSE
64       IF ( average_count_pr > 0 )  THEN
65          hom_sum = hom_sum / REAL( average_count_pr )
66       ELSE
67!
68!--       This case may happen if dt_dopr is changed in the d3par-list of
69!--       a restart run
70          RETURN
71       ENDIF
72    ENDIF
73
74   
75    IF ( myid == 0 )  THEN
76
77!
78!--    Plot-output for each (sub-)region
79
80!
81!--    Open file for profile output in NetCDF format
82       IF ( netcdf_output )  THEN
83          CALL check_open( 104 )
84       ENDIF
85
86!
87!--    Open PROFIL-output files for each (sub-)region
88       IF ( profil_output )  THEN
89          DO  sr = 0, statistic_regions
90             CALL check_open( 40 + sr )
91          ENDDO
92       ENDIF
93
94!
95!--    Increment the counter for number of output times
96       dopr_time_count = dopr_time_count + 1
97
98!
99!--    Re-set to zero the counter for the number of profiles already written
100!--    at the current output time into the respective crosses
101       cross_pnc_local = 0
102
103!
104!--    Output of initial profiles
105       IF ( dopr_time_count == 1 )  THEN
106
107          IF ( netcdf_output )  THEN
108#if defined( __netcdf )
109!
[197]110!--          Store initial time (t=0) to time axis, but only if an output
111!--          is required for at least one of the profiles
112             output_for_t0 = .FALSE.
113             DO  i = 1, dopr_n
114                IF ( dopr_initial_index(i) /= 0 )  THEN
115                   nc_stat = NF90_PUT_VAR( id_set_pr, id_var_time_pr,  &
116                                           (/ 0.0 /), start = (/ 1 /), &
117                                           count = (/ 1 /) )
118                   IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 329 )
119                   output_for_t0 = .TRUE.
120                   EXIT
121                ENDIF
122             ENDDO
[1]123
124!
125!--          Store normalization factors
126             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(1), &  ! wpt0
127                                  (/ hom_sum(nzb,18,normalizing_region) /), &
128                                     start = (/ 1 /), count = (/ 1 /) )
129             IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 330 )
130
131             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(2), &  ! ws2
[87]132                        (/ hom_sum(nzb+8,pr_palm,normalizing_region)**2 /), &
[1]133                                     start = (/ 1 /), count = (/ 1 /) )
134             IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 331 )
135
136             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(3), &  ! tsw2
[87]137                        (/ hom_sum(nzb+3,pr_palm,normalizing_region)**2 /), &
[1]138                                     start = (/ 1 /), count = (/ 1 /) )
139             IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 332 )
140
141             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(4), &  ! ws3
[87]142                        (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 /), &
[1]143                                     start = (/ 1 /), count = (/ 1 /) )
144             IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 333 )
145
146             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(5), &  ! ws2tsw
[87]147                        (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 *   &
148                           hom_sum(nzb+3,pr_palm,normalizing_region)    /), &
[1]149                                     start = (/ 1 /), count = (/ 1 /) )
150             IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 334 )
151
152             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(6), &  ! wstsw2
[87]153                        (/ hom_sum(nzb+8,pr_palm,normalizing_region) *      &
154                           hom_sum(nzb+3,pr_palm,normalizing_region)**2 /), &
[1]155                                     start = (/ 1 /), count = (/ 1 /) )
156             IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 335 )
157
158             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(7), &  ! z_i
[87]159                           (/ hom_sum(nzb+6,pr_palm,normalizing_region) /), &
[1]160                                     start = (/ 1 /), count = (/ 1 /) )
161             IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 336 )
162#endif
163          ENDIF
164!
165!--       Loop over all 1D variables
166          DO  i = 1, dopr_n
167
168             IF ( dopr_initial_index(i) /= 0 )  THEN
169
170!
171!--             Output for the individual (sub-)regions
172                DO  sr = 0, statistic_regions
173
174                   IF ( profil_output )  THEN
175                      id = 40 + sr
176!
177!--                   Write Label-Header
178                      WRITE ( id, 100 )  TRIM( data_output_pr(i) ), '(t=0)'
179!
180!--                   Write total profile
181                      DO  k = nzb, nzt+1
182                         WRITE ( id, 101 )  hom(k,2,dopr_initial_index(i),sr), &
183                                            hom(k,1,dopr_initial_index(i),sr)
184                      ENDDO
185!
186!--                   Write separation label
187                      WRITE ( id, 102 )
188                   ENDIF
189
190                   IF ( netcdf_output )  THEN
191#if defined( __netcdf )
192!
193!--                   Write data to netcdf file
194                      nc_stat = NF90_PUT_VAR( id_set_pr, id_var_dopr(i,sr),    &
195                                    hom(nzb:nzt+1,1,dopr_initial_index(i),sr), &
196                                              start = (/ 1, 1 /),              &
197                                              count = (/ nzt-nzb+2, 1 /) )
198                      IF ( nc_stat /= NF90_NOERR )  &
199                                                CALL handle_netcdf_error( 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) = &
[87]258                             ( hom_sum(nzb+3,pr_palm,normalizing_region) )**2
[1]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) = &
[87]264                             hom_sum(nzb+8,pr_palm,normalizing_region)  &
265                           * ( hom_sum(nzb+3,pr_palm,normalizing_region) )**2
[1]266                         CASE ( 'ws2' )
267                            cross_normx_factor(k,j) = &
[87]268                             ( hom_sum(nzb+8,pr_palm,normalizing_region) )**2
[1]269                         CASE ( 'ws2ts' )
270                            cross_normx_factor(k,j) = &
[87]271                           ( hom_sum(nzb+8,pr_palm,normalizing_region) )**2 &
272                           * hom_sum(nzb+3,pr_palm,normalizing_region)
[1]273                         CASE ( 'ws3' )
274                            cross_normx_factor(k,j) = &
[87]275                             ( hom_sum(nzb+8,pr_palm,normalizing_region) )**3
[1]276
277                      END SELECT
278
279                      SELECT CASE ( cross_normalized_y(j) )
280
281                         CASE ( 'z_i' )
282                            cross_normy_factor(k,j) = &
[87]283                                    hom_sum(nzb+6,pr_palm,normalizing_region)
[1]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                         PRINT*,'+++ WARNING data_output_profiles: normalizi', &
293                                'ng cross ',j, ' is not possible since one o', &
294                                'f the'
295                         PRINT*,'                     normalizing factors is ',&
296                                'zero!'
297                         PRINT*,'    cross_normx_factor(',k,',',j,') = ', &
298                                cross_normx_factor(k,j)
299                         PRINT*,'    cross_normy_factor(',k,',',j,') = ', &
300                                cross_normy_factor(k,j)
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
[197]349          IF ( netcdf_output  .AND.  output_for_t0 )  THEN
350             dopr_time_count = dopr_time_count + 1
351          ENDIF
[1]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
[87]374                        (/ hom_sum(nzb+8,pr_palm,normalizing_region)**2 /), &
[1]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
[87]380                        (/ hom_sum(nzb+3,pr_palm,normalizing_region)**2 /), &
[1]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
[87]386                        (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 /), &
[1]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
[87]392                        (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 *   &
393                           hom_sum(nzb+3,pr_palm,normalizing_region)    /), &
[1]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
[87]399                        (/ hom_sum(nzb+8,pr_palm,normalizing_region) *      &
400                           hom_sum(nzb+3,pr_palm,normalizing_region)**2 /), &
[1]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
[87]406                           (/ hom_sum(nzb+6,pr_palm,normalizing_region) /), &
[1]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) = &
[87]505                            ( hom_sum(nzb+11,pr_palm,normalizing_region) )**2
[1]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) = &
[87]511                              hom_sum(nzb+8,pr_palm,normalizing_region)  &
512                          * ( hom_sum(nzb+11,pr_palm,normalizing_region) )**2
[1]513                   CASE ( 'ws2' )
514                      cross_normx_factor(k,j) = &
[87]515                            ( hom_sum(nzb+8,pr_palm,normalizing_region) )**2
[1]516                   CASE ( 'ws2tsw' )
517                      cross_normx_factor(k,j) = &
[87]518                            ( hom_sum(nzb+8,pr_palm,normalizing_region) )**2&
519                            * hom_sum(nzb+11,pr_palm,normalizing_region)
[1]520                   CASE ( 'ws3' )
521                      cross_normx_factor(k,j) = &
[87]522                            ( hom_sum(nzb+8,pr_palm,normalizing_region) )**3
[1]523
524                END SELECT
525                SELECT CASE ( cross_normalized_y(j) )
526
527                   CASE ( 'z_i' )
528                      cross_normy_factor(k,j) = &
[87]529                                   hom_sum(nzb+6,pr_palm,normalizing_region)
[1]530
531                END SELECT
532
533!
534!--             Check the normalizing factors for zeros and deactivate the
535!--             normalization, if required.
536                IF ( cross_normx_factor(k,j) == 0.0  .OR. &
537                     cross_normy_factor(k,j) == 0.0 )  THEN
538                   PRINT*,'+++ WARNING data_output_profiles: normalizing ',j, &
539                          ' cross is not possible since one of the'
540                   PRINT*,'                     normalizing factors is zero!'
541                   PRINT*,'    cross_normx_factor(',k,',',j,') = ', &
542                           cross_normx_factor(k,j)
543                   PRINT*,'    cross_normy_factor(',k,',',j,') = ', &
544                           cross_normy_factor(k,j)
545                   cross_normx_factor(k,j) = 1.0
546                   cross_normy_factor(k,j) = 1.0
547                   cross_normalized_x(j) = ' '
548                   cross_normalized_y(j) = ' '
549                ENDIF
550
551!
552!--             If required, extend normalized x-value range of the respective 
553!--             cross, provided it has not been specified in check_parameters.
554!--             Determination over all (sub-)regions.
555                IF ( cross_uxmin_normalized(j) == 0.0  .AND. &
556                     cross_uxmax_normalized(j) == 0.0 )  THEN
557
558                   DO  sr = 0, statistic_regions
559
560                      uxmi = MINVAL( hom(:nz_do1d,1,dopr_index(i),sr) ) / &
561                             cross_normx_factor(k,j)
562                      uxma = MAXVAL( hom(:nz_do1d,1,dopr_index(i),sr) ) / &
563                             cross_normx_factor(k,j)
564!
565!--                   When the value range of the first line in the
566!--                   corresponding cross is determined, its value range is
567!--                   simply adopted.
568                      IF ( cross_uxmin_normalized_computed(j) > &
569                           cross_uxmax_normalized_computed(j) )  THEN
570                         cross_uxmin_normalized_computed(j) = uxmi
571                         cross_uxmax_normalized_computed(j) = uxma
572                      ELSE
573                         cross_uxmin_normalized_computed(j) = &
574                                MIN( cross_uxmin_normalized_computed(j), uxmi )
575                         cross_uxmax_normalized_computed(j) = &
576                                MAX( cross_uxmax_normalized_computed(j), uxma )
577                      ENDIF
578
579                   ENDDO
580
581                ENDIF
582
583             ENDIF   ! Index determination
584
585          ENDIF   ! profil output
586
587       ENDDO   ! Loop over dopr_n
588
589    ENDIF  ! Output on PE0
590
591!
592!-- If averaging has been done above, the summation counter must be re-set.
593    IF ( averaging_interval_pr /= 0.0 )  THEN
594       average_count_pr = 0
595    ENDIF
596
597    CALL cpu_log( log_point(15), 'data_output_profiles','stop', 'nobarrier' )
598
599!
600!-- Formats
601100 FORMAT ('#1 ',A,1X,A)
602101 FORMAT (E15.7,1X,E15.7)
603102 FORMAT ('NEXT')
604
605 END SUBROUTINE data_output_profiles
Note: See TracBrowser for help on using the repository browser.