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

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

Output of NetCDF messages with aid of message handling routine.

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