source: palm/trunk/SOURCE/data_output_2d.f90 @ 354

Last change on this file since 354 was 354, checked in by maronga, 15 years ago

xy cross section output of sensible and latent heatflux is now available

  • Property svn:keywords set to Id
File size: 48.6 KB
Line 
1 SUBROUTINE data_output_2d( mode, av )
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! Bugfix: averaging along z is not allowed for 2d quantities (e.g. u* and z0)
9! Output of messages replaced by message handling routine.
10! Output of user defined 2D (XY) arrays at z=nzb+1 is now possible
11!
12!
13! Former revisions:
14! -----------------
15! $Id: data_output_2d.f90 354 2009-07-13 13:14:25Z maronga $
16!
17! 215 2008-11-18 09:54:31Z raasch
18! Bugfix: no output of particle concentration and radius unless particles
19! have been started
20!
21! 96 2007-06-04 08:07:41Z raasch
22! Output of density and salinity
23!
24! 75 2007-03-22 09:54:05Z raasch
25! Output of precipitation amount/rate and roughness length,
26! 2nd+3rd argument removed from exchange horiz
27!
28! RCS Log replace by Id keyword, revision history cleaned up
29!
30! Revision 1.5  2006/08/22 13:50:29  raasch
31! xz and yz cross sections now up to nzt+1
32!
33! Revision 1.2  2006/02/23 10:19:22  raasch
34! Output of time-averaged data, output of averages along x, y, or z,
35! output of user-defined quantities,
36! section data are copied from local_pf to local_2d before they are output,
37! output of particle concentration and mean radius,
38! Former subroutine plot_2d renamed data_output_2d, pl2d.. renamed do2d..,
39! anz renamed ngp, ebene renamed section, pl2d_.._anz renamed do2d_.._n
40!
41! Revision 1.1  1997/08/11 06:24:09  raasch
42! Initial revision
43!
44!
45! Description:
46! ------------
47! Data output of horizontal cross-sections in NetCDF format or binary format
48! compatible to old graphic software iso2d.
49! Attention: The position of the sectional planes is still not always computed
50! ---------  correctly. (zu is used always)!
51!------------------------------------------------------------------------------!
52
53    USE arrays_3d
54    USE averaging
55    USE cloud_parameters
56    USE control_parameters
57    USE cpulog
58    USE grid_variables
59    USE indices
60    USE interfaces
61    USE netcdf_control
62    USE particle_attributes
63    USE pegrid
64
65    IMPLICIT NONE
66
67    CHARACTER (LEN=2)  ::  do2d_mode, mode
68    CHARACTER (LEN=4)  ::  grid
69    CHARACTER (LEN=25) ::  section_chr
70    CHARACTER (LEN=50) ::  rtext
71    INTEGER ::  av, ngp, file_id, i, if, is, j, k, l, layer_xy, n, psi, s, &
72                sender, &
73                ind(4)
74    LOGICAL ::  found, resorted, two_d
75    REAL    ::  mean_r, s_r3, s_r4
76    REAL, DIMENSION(:), ALLOCATABLE ::      level_z
77    REAL, DIMENSION(:,:), ALLOCATABLE ::    local_2d, local_2d_l
78    REAL, DIMENSION(:,:,:), ALLOCATABLE ::  local_pf
79#if defined( __parallel )
80    REAL, DIMENSION(:,:),   ALLOCATABLE ::  total_2d
81#endif
82    REAL, DIMENSION(:,:,:), POINTER ::  to_be_resorted
83
84    NAMELIST /LOCAL/  rtext
85
86    CALL cpu_log (log_point(3),'data_output_2d','start')
87
88!
89!-- Immediate return, if no output is requested (no respective sections
90!-- found in parameter data_output)
91    IF ( mode == 'xy'  .AND.  .NOT. data_output_xy(av) )  RETURN
92    IF ( mode == 'xz'  .AND.  .NOT. data_output_xz(av) )  RETURN
93    IF ( mode == 'yz'  .AND.  .NOT. data_output_yz(av) )  RETURN
94
95    two_d = .FALSE.    ! local variable to distinguish between output of pure 2D
96                       ! arrays and cross-sections of 3D arrays.
97
98!
99!-- Depending on the orientation of the cross-section, the respective output
100!-- files have to be opened.
101    SELECT CASE ( mode )
102
103       CASE ( 'xy' )
104
105          s = 1
106          ALLOCATE( level_z(0:nzt+1), local_2d(nxl-1:nxr+1,nys-1:nyn+1) )
107
108#if defined( __netcdf )
109          IF ( myid == 0  .AND.  netcdf_output )  CALL check_open( 101+av*10 )
110#endif
111
112          IF ( data_output_2d_on_each_pe )  THEN
113             CALL check_open( 21 )
114          ELSE
115             IF ( myid == 0 )  THEN
116                IF ( iso2d_output )  CALL check_open( 21 )
117#if defined( __parallel )
118                ALLOCATE( total_2d(-1:nx+1,-1:ny+1) )
119#endif
120             ENDIF
121          ENDIF
122
123       CASE ( 'xz' )
124
125          s = 2
126          ALLOCATE( local_2d(nxl-1:nxr+1,nzb:nzt+1) )
127
128#if defined( __netcdf )
129          IF ( myid == 0  .AND.  netcdf_output )  CALL check_open( 102+av*10 )
130#endif
131
132          IF ( data_output_2d_on_each_pe )  THEN
133             CALL check_open( 22 )
134          ELSE
135             IF ( myid == 0 )  THEN
136                IF ( iso2d_output )  CALL check_open( 22 )
137#if defined( __parallel )
138                ALLOCATE( total_2d(-1:nx+1,nzb:nzt+1) )
139#endif
140             ENDIF
141          ENDIF
142
143       CASE ( 'yz' )
144
145          s = 3
146          ALLOCATE( local_2d(nys-1:nyn+1,nzb:nzt+1) )
147
148#if defined( __netcdf )
149          IF ( myid == 0  .AND.  netcdf_output )  CALL check_open( 103+av*10 )
150#endif
151
152          IF ( data_output_2d_on_each_pe )  THEN
153             CALL check_open( 23 )
154          ELSE
155             IF ( myid == 0 )  THEN
156                IF ( iso2d_output )  CALL check_open( 23 )
157#if defined( __parallel )
158                ALLOCATE( total_2d(-1:ny+1,nzb:nzt+1) )
159#endif
160             ENDIF
161          ENDIF
162
163       CASE DEFAULT
164
165          message_string = 'unknown cross-section: ' // TRIM( mode )
166          CALL message( 'data_output_2d', 'PA0180', 1, 2, 0, 6, 0 )
167
168    END SELECT
169
170!
171!-- Allocate a temporary array for resorting (kji -> ijk).
172    ALLOCATE( local_pf(nxl-1:nxr+1,nys-1:nyn+1,nzb:nzt+1) )
173
174!
175!-- Loop of all variables to be written.
176!-- Output dimensions chosen
177    if = 1
178    l = MAX( 2, LEN_TRIM( do2d(av,if) ) )
179    do2d_mode = do2d(av,if)(l-1:l)
180
181    DO  WHILE ( do2d(av,if)(1:1) /= ' ' )
182
183       IF ( do2d_mode == mode )  THEN
184!
185!--       Store the array chosen on the temporary array.
186          resorted = .FALSE.
187          SELECT CASE ( TRIM( do2d(av,if) ) )
188
189             CASE ( 'e_xy', 'e_xz', 'e_yz' )
190                IF ( av == 0 )  THEN
191                   to_be_resorted => e
192                ELSE
193                   to_be_resorted => e_av
194                ENDIF
195                IF ( mode == 'xy' )  level_z = zu
196
197             CASE ( 'lwp*_xy' )        ! 2d-array
198                IF ( av == 0 )  THEN
199                   DO  i = nxl-1, nxr+1
200                      DO  j = nys-1, nyn+1
201                         local_pf(i,j,nzb+1) = SUM( ql(nzb:nzt,j,i) * &
202                                                    dzw(1:nzt+1) )
203                      ENDDO
204                   ENDDO
205                ELSE
206                   DO  i = nxl-1, nxr+1
207                      DO  j = nys-1, nyn+1
208                         local_pf(i,j,nzb+1) = lwp_av(j,i)
209                      ENDDO
210                   ENDDO
211                ENDIF
212                resorted = .TRUE.
213                two_d = .TRUE.
214                level_z(nzb+1) = zu(nzb+1)
215
216             CASE ( 'p_xy', 'p_xz', 'p_yz' )
217                IF ( av == 0 )  THEN
218                   to_be_resorted => p
219                ELSE
220                   to_be_resorted => p_av
221                ENDIF
222                IF ( mode == 'xy' )  level_z = zu
223
224             CASE ( 'pc_xy', 'pc_xz', 'pc_yz' )  ! particle concentration
225                IF ( av == 0 )  THEN
226                   IF ( simulated_time >= particle_advection_start )  THEN
227                      tend = prt_count
228                      CALL exchange_horiz( tend )
229                   ELSE
230                      tend = 0.0
231                   ENDIF
232                   DO  i = nxl-1, nxr+1
233                      DO  j = nys-1, nyn+1
234                         DO  k = nzb, nzt+1
235                            local_pf(i,j,k) = tend(k,j,i)
236                         ENDDO
237                      ENDDO
238                   ENDDO
239                   resorted = .TRUE.
240                ELSE
241                   CALL exchange_horiz( pc_av )
242                   to_be_resorted => pc_av
243                ENDIF
244
245             CASE ( 'pr_xy', 'pr_xz', 'pr_yz' )  ! mean particle radius
246                IF ( av == 0 )  THEN
247                   IF ( simulated_time >= particle_advection_start )  THEN
248                      DO  i = nxl, nxr
249                         DO  j = nys, nyn
250                            DO  k = nzb, nzt+1
251                               psi = prt_start_index(k,j,i)
252                               s_r3 = 0.0
253                               s_r4 = 0.0
254                               DO  n = psi, psi+prt_count(k,j,i)-1
255                                  s_r3 = s_r3 + particles(n)%radius**3
256                                  s_r4 = s_r4 + particles(n)%radius**4
257                               ENDDO
258                               IF ( s_r3 /= 0.0 )  THEN
259                                  mean_r = s_r4 / s_r3
260                               ELSE
261                                  mean_r = 0.0
262                               ENDIF
263                               tend(k,j,i) = mean_r
264                            ENDDO
265                         ENDDO
266                      ENDDO
267                      CALL exchange_horiz( tend )
268                   ELSE
269                      tend = 0.0
270                   ENDIF
271                   DO  i = nxl-1, nxr+1
272                      DO  j = nys-1, nyn+1
273                         DO  k = nzb, nzt+1
274                            local_pf(i,j,k) = tend(k,j,i)
275                         ENDDO
276                      ENDDO
277                   ENDDO
278                   resorted = .TRUE.
279                ELSE
280                   CALL exchange_horiz( pr_av )
281                   to_be_resorted => pr_av
282                ENDIF
283
284             CASE ( 'pra*_xy' )        ! 2d-array / integral quantity => no av
285                CALL exchange_horiz_2d( precipitation_amount )
286                DO  i = nxl-1, nxr+1
287                   DO  j = nys-1, nyn+1
288                      local_pf(i,j,nzb+1) =  precipitation_amount(j,i)
289                   ENDDO
290                ENDDO
291                precipitation_amount = 0.0   ! reset for next integ. interval
292                resorted = .TRUE.
293                two_d = .TRUE.
294                level_z(nzb+1) = zu(nzb+1)
295
296             CASE ( 'prr*_xy' )        ! 2d-array
297                IF ( av == 0 )  THEN
298                   CALL exchange_horiz_2d( precipitation_rate )
299                   DO  i = nxl-1, nxr+1
300                      DO  j = nys-1, nyn+1 
301                         local_pf(i,j,nzb+1) =  precipitation_rate(j,i)
302                      ENDDO
303                   ENDDO
304                ELSE
305                   CALL exchange_horiz_2d( precipitation_rate_av )
306                   DO  i = nxl-1, nxr+1
307                      DO  j = nys-1, nyn+1 
308                         local_pf(i,j,nzb+1) =  precipitation_rate_av(j,i)
309                      ENDDO
310                   ENDDO
311                ENDIF
312                resorted = .TRUE.
313                two_d = .TRUE.
314                level_z(nzb+1) = zu(nzb+1)
315
316             CASE ( 'pt_xy', 'pt_xz', 'pt_yz' )
317                IF ( av == 0 )  THEN
318                   IF ( .NOT. cloud_physics ) THEN
319                      to_be_resorted => pt
320                   ELSE
321                      DO  i = nxl-1, nxr+1
322                         DO  j = nys-1, nyn+1
323                            DO  k = nzb, nzt+1
324                               local_pf(i,j,k) = pt(k,j,i) + l_d_cp *    &
325                                                             pt_d_t(k) * &
326                                                             ql(k,j,i)
327                            ENDDO
328                         ENDDO
329                      ENDDO
330                      resorted = .TRUE.
331                   ENDIF
332                ELSE
333                   to_be_resorted => pt_av
334                ENDIF
335                IF ( mode == 'xy' )  level_z = zu
336
337             CASE ( 'q_xy', 'q_xz', 'q_yz' )
338                IF ( av == 0 )  THEN
339                   to_be_resorted => q
340                ELSE
341                   to_be_resorted => q_av
342                ENDIF
343                IF ( mode == 'xy' )  level_z = zu
344
345             CASE ( 'ql_xy', 'ql_xz', 'ql_yz' )
346                IF ( av == 0 )  THEN
347                   to_be_resorted => ql
348                ELSE
349                   to_be_resorted => ql_av
350                ENDIF
351                IF ( mode == 'xy' )  level_z = zu
352
353             CASE ( 'ql_c_xy', 'ql_c_xz', 'ql_c_yz' )
354                IF ( av == 0 )  THEN
355                   to_be_resorted => ql_c
356                ELSE
357                   to_be_resorted => ql_c_av
358                ENDIF
359                IF ( mode == 'xy' )  level_z = zu
360
361             CASE ( 'ql_v_xy', 'ql_v_xz', 'ql_v_yz' )
362                IF ( av == 0 )  THEN
363                   to_be_resorted => ql_v
364                ELSE
365                   to_be_resorted => ql_v_av
366                ENDIF
367                IF ( mode == 'xy' )  level_z = zu
368
369             CASE ( 'ql_vp_xy', 'ql_vp_xz', 'ql_vp_yz' )
370                IF ( av == 0 )  THEN
371                   to_be_resorted => ql_vp
372                ELSE
373                   to_be_resorted => ql_vp_av
374                ENDIF
375                IF ( mode == 'xy' )  level_z = zu
376
377             CASE ( 'qsws*_xy' )        ! 2d-array
378                IF ( av == 0 ) THEN
379                   DO  i = nxl-1, nxr+1
380                      DO  j = nys-1, nyn+1 
381                         local_pf(i,j,nzb+1) =  qsws(j,i)
382                      ENDDO
383                   ENDDO
384                ELSE
385                   DO  i = nxl-1, nxr+1
386                      DO  j = nys-1, nyn+1 
387                         local_pf(i,j,nzb+1) =  qsws_av(j,i)
388                      ENDDO
389                   ENDDO
390                ENDIF
391                resorted = .TRUE.
392                two_d = .TRUE.
393                level_z(nzb+1) = zu(nzb+1)
394
395             CASE ( 'qv_xy', 'qv_xz', 'qv_yz' )
396                IF ( av == 0 )  THEN
397                   DO  i = nxl-1, nxr+1
398                      DO  j = nys-1, nyn+1
399                         DO  k = nzb, nzt+1
400                            local_pf(i,j,k) = q(k,j,i) - ql(k,j,i)
401                         ENDDO
402                      ENDDO
403                   ENDDO
404                   resorted = .TRUE.
405                ELSE
406                   to_be_resorted => qv_av
407                ENDIF
408                IF ( mode == 'xy' )  level_z = zu
409
410             CASE ( 'rho_xy', 'rho_xz', 'rho_yz' )
411                IF ( av == 0 )  THEN
412                   to_be_resorted => rho
413                ELSE
414                   to_be_resorted => rho_av
415                ENDIF
416
417             CASE ( 's_xy', 's_xz', 's_yz' )
418                IF ( av == 0 )  THEN
419                   to_be_resorted => q
420                ELSE
421                   to_be_resorted => q_av
422                ENDIF
423
424             CASE ( 'sa_xy', 'sa_xz', 'sa_yz' )
425                IF ( av == 0 )  THEN
426                   to_be_resorted => sa
427                ELSE
428                   to_be_resorted => sa_av
429                ENDIF
430
431             CASE ( 'shf*_xy' )        ! 2d-array
432                IF ( av == 0 ) THEN
433                   DO  i = nxl-1, nxr+1
434                      DO  j = nys-1, nyn+1 
435                         local_pf(i,j,nzb+1) =  shf(j,i)
436                      ENDDO
437                   ENDDO
438                ELSE
439                   DO  i = nxl-1, nxr+1
440                      DO  j = nys-1, nyn+1 
441                         local_pf(i,j,nzb+1) =  shf_av(j,i)
442                      ENDDO
443                   ENDDO
444                ENDIF
445                resorted = .TRUE.
446                two_d = .TRUE.
447                level_z(nzb+1) = zu(nzb+1)
448
449             CASE ( 't*_xy' )        ! 2d-array
450                IF ( av == 0 )  THEN
451                   DO  i = nxl-1, nxr+1
452                      DO  j = nys-1, nyn+1
453                         local_pf(i,j,nzb+1) = ts(j,i)
454                      ENDDO
455                   ENDDO
456                ELSE
457                   DO  i = nxl-1, nxr+1
458                      DO  j = nys-1, nyn+1
459                         local_pf(i,j,nzb+1) = ts_av(j,i)
460                      ENDDO
461                   ENDDO
462                ENDIF
463                resorted = .TRUE.
464                two_d = .TRUE.
465                level_z(nzb+1) = zu(nzb+1)
466
467             CASE ( 'u_xy', 'u_xz', 'u_yz' )
468                IF ( av == 0 )  THEN
469                   to_be_resorted => u
470                ELSE
471                   to_be_resorted => u_av
472                ENDIF
473                IF ( mode == 'xy' )  level_z = zu
474!
475!--             Substitute the values generated by "mirror" boundary condition
476!--             at the bottom boundary by the real surface values.
477                IF ( do2d(av,if) == 'u_xz'  .OR.  do2d(av,if) == 'u_yz' )  THEN
478                   IF ( ibc_uv_b == 0 )  local_pf(:,:,nzb) = 0.0
479                ENDIF
480
481             CASE ( 'u*_xy' )        ! 2d-array
482                IF ( av == 0 )  THEN
483                   DO  i = nxl-1, nxr+1
484                      DO  j = nys-1, nyn+1
485                         local_pf(i,j,nzb+1) = us(j,i)
486                      ENDDO
487                   ENDDO
488                ELSE
489                   DO  i = nxl-1, nxr+1
490                      DO  j = nys-1, nyn+1
491                         local_pf(i,j,nzb+1) = us_av(j,i)
492                      ENDDO
493                   ENDDO
494                ENDIF
495                resorted = .TRUE.
496                two_d = .TRUE.
497                level_z(nzb+1) = zu(nzb+1)
498
499             CASE ( 'v_xy', 'v_xz', 'v_yz' )
500                IF ( av == 0 )  THEN
501                   to_be_resorted => v
502                ELSE
503                   to_be_resorted => v_av
504                ENDIF
505                IF ( mode == 'xy' )  level_z = zu
506!
507!--             Substitute the values generated by "mirror" boundary condition
508!--             at the bottom boundary by the real surface values.
509                IF ( do2d(av,if) == 'v_xz'  .OR.  do2d(av,if) == 'v_yz' )  THEN
510                   IF ( ibc_uv_b == 0 )  local_pf(:,:,nzb) = 0.0
511                ENDIF
512
513             CASE ( 'vpt_xy', 'vpt_xz', 'vpt_yz' )
514                IF ( av == 0 )  THEN
515                   to_be_resorted => vpt
516                ELSE
517                   to_be_resorted => vpt_av
518                ENDIF
519                IF ( mode == 'xy' )  level_z = zu
520
521             CASE ( 'w_xy', 'w_xz', 'w_yz' )
522                IF ( av == 0 )  THEN
523                   to_be_resorted => w
524                ELSE
525                   to_be_resorted => w_av
526                ENDIF
527                IF ( mode == 'xy' )  level_z = zw
528
529             CASE ( 'z0*_xy' )        ! 2d-array
530                IF ( av == 0 ) THEN
531                   DO  i = nxl-1, nxr+1
532                      DO  j = nys-1, nyn+1 
533                         local_pf(i,j,nzb+1) =  z0(j,i)
534                      ENDDO
535                   ENDDO
536                ELSE
537                   DO  i = nxl-1, nxr+1
538                      DO  j = nys-1, nyn+1 
539                         local_pf(i,j,nzb+1) =  z0_av(j,i)
540                      ENDDO
541                   ENDDO
542                ENDIF
543                resorted = .TRUE.
544                two_d = .TRUE.
545                level_z(nzb+1) = zu(nzb+1)
546
547             CASE DEFAULT
548!
549!--             User defined quantity
550                CALL user_data_output_2d( av, do2d(av,if), found, grid, &
551                                          local_pf, two_d )
552                resorted = .TRUE.
553
554                IF ( grid == 'zu' )  THEN
555                   IF ( mode == 'xy' )  level_z = zu
556                ELSEIF ( grid == 'zw' )  THEN
557                   IF ( mode == 'xy' )  level_z = zw
558                ELSEIF ( grid == 'zu1' ) THEN
559                   IF ( mode == 'xy' )  level_z(nzb+1) = zu(nzb+1)
560                ENDIF
561
562                IF ( .NOT. found )  THEN
563                   message_string = 'no output provided for: ' //    &
564                                    TRIM( do2d(av,if) )
565                   CALL message( 'data_output_2d', 'PA0181', 0, 0, 0, 6, 0 )
566                ENDIF
567
568          END SELECT
569
570!
571!--       Resort the array to be output, if not done above
572          IF ( .NOT. resorted )  THEN
573             DO  i = nxl-1, nxr+1
574                DO  j = nys-1, nyn+1
575                   DO  k = nzb, nzt+1
576                      local_pf(i,j,k) = to_be_resorted(k,j,i)
577                   ENDDO
578                ENDDO
579             ENDDO
580          ENDIF
581
582!
583!--       Output of the individual cross-sections, depending on the cross-
584!--       section mode chosen.
585          is = 1
586   loop1: DO  WHILE ( section(is,s) /= -9999  .OR.  two_d )
587
588             SELECT CASE ( mode )
589
590                CASE ( 'xy' )
591!
592!--                Determine the cross section index
593                   IF ( two_d )  THEN
594                      layer_xy = nzb+1
595                   ELSE
596                      layer_xy = section(is,s)
597                   ENDIF
598
599!
600!--                Update the NetCDF xy cross section time axis
601                   IF ( myid == 0 )  THEN
602                      IF ( simulated_time /= do2d_xy_last_time(av) )  THEN
603                         do2d_xy_time_count(av) = do2d_xy_time_count(av) + 1
604                         do2d_xy_last_time(av)  = simulated_time
605                         IF ( .NOT. data_output_2d_on_each_pe  .AND. &
606                              netcdf_output )  THEN
607#if defined( __netcdf )
608                            nc_stat = NF90_PUT_VAR( id_set_xy(av),             &
609                                                    id_var_time_xy(av),        &
610                                             (/ time_since_reference_point /), &
611                                         start = (/ do2d_xy_time_count(av) /), &
612                                                    count = (/ 1 /) )
613                         CALL handle_netcdf_error( 'data_output_2d', 53 )
614#endif
615                         ENDIF
616                      ENDIF
617                   ENDIF
618!
619!--                If required, carry out averaging along z
620                   IF ( section(is,s) == -1  .AND.  .NOT. two_d )  THEN
621
622                      local_2d = 0.0
623!
624!--                   Carry out the averaging (all data are on the PE)
625                      DO  k = nzb, nzt+1
626                         DO  j = nys-1, nyn+1
627                            DO  i = nxl-1, nxr+1
628                               local_2d(i,j) = local_2d(i,j) + local_pf(i,j,k)
629                            ENDDO
630                         ENDDO
631                      ENDDO
632
633                      local_2d = local_2d / ( nzt -nzb + 2.0 )
634
635                   ELSE
636!
637!--                   Just store the respective section on the local array
638                      local_2d = local_pf(:,:,layer_xy)
639
640                   ENDIF
641
642#if defined( __parallel )
643                   IF ( data_output_2d_on_each_pe )  THEN
644!
645!--                   Output of partial arrays on each PE
646#if defined( __netcdf )
647                      IF ( netcdf_output  .AND.  myid == 0 )  THEN
648                         WRITE ( 21 )  simulated_time, do2d_xy_time_count(av), &
649                                       av
650                      ENDIF
651#endif
652                      WRITE ( 21 )  nxl-1, nxr+1, nys-1, nyn+1
653                      WRITE ( 21 )  local_2d
654
655                   ELSE
656!
657!--                   PE0 receives partial arrays from all processors and then
658!--                   outputs them. Here a barrier has to be set, because
659!--                   otherwise "-MPI- FATAL: Remote protocol queue full" may
660!--                   occur.
661                      CALL MPI_BARRIER( comm2d, ierr )
662
663                      ngp = ( nxr-nxl+3 ) * ( nyn-nys+3 )
664                      IF ( myid == 0 )  THEN
665!
666!--                      Local array can be relocated directly.
667                         total_2d(nxl-1:nxr+1,nys-1:nyn+1) = local_2d
668!
669!--                      Receive data from all other PEs.
670                         DO  n = 1, numprocs-1
671!
672!--                         Receive index limits first, then array.
673!--                         Index limits are received in arbitrary order from
674!--                         the PEs.
675                            CALL MPI_RECV( ind(1), 4, MPI_INTEGER,            &
676                                           MPI_ANY_SOURCE, 0, comm2d, status, &
677                                           ierr )
678                            sender = status(MPI_SOURCE)
679                            DEALLOCATE( local_2d )
680                            ALLOCATE( local_2d(ind(1):ind(2),ind(3):ind(4)) )
681                            CALL MPI_RECV( local_2d(ind(1),ind(3)), ngp,      &
682                                           MPI_REAL, sender, 1, comm2d,       &
683                                           status, ierr )
684                            total_2d(ind(1):ind(2),ind(3):ind(4)) = local_2d
685                         ENDDO
686!
687!--                      Output of the total cross-section.
688                         IF ( iso2d_output ) WRITE (21)  total_2d(0:nx+1,0:ny+1)
689!
690!--                      Relocate the local array for the next loop increment
691                         DEALLOCATE( local_2d )
692                         ALLOCATE( local_2d(nxl-1:nxr+1,nys-1:nyn+1) )
693
694#if defined( __netcdf )
695                         IF ( netcdf_output )  THEN
696                            IF ( two_d ) THEN
697                               nc_stat = NF90_PUT_VAR( id_set_xy(av),          &
698                                                       id_var_do2d(av,if),     &
699                                                      total_2d(0:nx+1,0:ny+1), &
700                                start = (/ 1, 1, 1, do2d_xy_time_count(av) /), &
701                                                count = (/ nx+2, ny+2, 1, 1 /) )
702                            ELSE
703                               nc_stat = NF90_PUT_VAR( id_set_xy(av),          &
704                                                       id_var_do2d(av,if),     &
705                                                      total_2d(0:nx+1,0:ny+1), &
706                               start = (/ 1, 1, is, do2d_xy_time_count(av) /), &
707                                                count = (/ nx+2, ny+2, 1, 1 /) )
708                            ENDIF
709                            CALL handle_netcdf_error( 'data_output_2d', 54 )
710                         ENDIF
711#endif
712
713                      ELSE
714!
715!--                      First send the local index limits to PE0
716                         ind(1) = nxl-1; ind(2) = nxr+1
717                         ind(3) = nys-1; ind(4) = nyn+1
718                         CALL MPI_SEND( ind(1), 4, MPI_INTEGER, 0, 0, comm2d, &
719                                        ierr )
720!
721!--                      Send data to PE0
722                         CALL MPI_SEND( local_2d(nxl-1,nys-1), ngp, MPI_REAL, &
723                                        0, 1, comm2d, ierr )
724                      ENDIF
725!
726!--                   A barrier has to be set, because otherwise some PEs may
727!--                   proceed too fast so that PE0 may receive wrong data on
728!--                   tag 0
729                      CALL MPI_BARRIER( comm2d, ierr )
730                   ENDIF
731#else
732                   IF ( iso2d_output )  THEN
733                      WRITE (21)  local_2d(nxl:nxr+1,nys:nyn+1)
734                   ENDIF
735#if defined( __netcdf )
736                   IF ( netcdf_output )  THEN
737                      IF ( two_d ) THEN
738                         nc_stat = NF90_PUT_VAR( id_set_xy(av),                &
739                                                 id_var_do2d(av,if),           &
740                                                local_2d(nxl:nxr+1,nys:nyn+1), &
741                                start = (/ 1, 1, 1, do2d_xy_time_count(av) /), &
742                                              count = (/ nx+2, ny+2, 1, 1 /) )
743                      ELSE
744                         nc_stat = NF90_PUT_VAR( id_set_xy(av),                &
745                                                 id_var_do2d(av,if),           &
746                                                local_2d(nxl:nxr+1,nys:nyn+1), &
747                               start = (/ 1, 1, is, do2d_xy_time_count(av) /), &
748                                              count = (/ nx+2, ny+2, 1, 1 /) )
749                      ENDIF
750                      CALL handle_netcdf_error( 'data_output_2d', 55 )
751                   ENDIF
752#endif
753#endif
754                   do2d_xy_n = do2d_xy_n + 1
755!
756!--                Write LOCAL parameter set for ISO2D.
757                   IF ( myid == 0  .AND.  iso2d_output )  THEN
758                      IF ( section(is,s) /= -1 )  THEN
759                         WRITE ( section_chr, '(''z = '',F7.2,'' m  (GP '',I3, &
760                                               &'')'')'                        &
761                               )  level_z(layer_xy), layer_xy
762                      ELSE
763                         section_chr = 'averaged along z'
764                      ENDIF
765                      IF ( av == 0 )  THEN
766                         rtext = TRIM( do2d(av,if) ) // '  t = ' //    &
767                                 TRIM( simulated_time_chr ) // '  ' // &
768                                 TRIM( section_chr )
769                      ELSE
770                         rtext = TRIM( do2d(av,if) ) // '  averaged t = ' // &
771                                 TRIM( simulated_time_chr ) // '  ' //       &
772                                 TRIM( section_chr )
773                      ENDIF
774                      WRITE (27,LOCAL)
775                   ENDIF
776!
777!--                For 2D-arrays (e.g. u*) only one cross-section is available.
778!--                Hence exit loop of output levels.
779                   IF ( two_d )  THEN
780                      two_d = .FALSE.
781                      EXIT loop1
782                   ENDIF
783
784                CASE ( 'xz' )
785!
786!--                Update the NetCDF xz cross section time axis
787                   IF ( myid == 0 )  THEN
788                      IF ( simulated_time /= do2d_xz_last_time(av) )  THEN
789                         do2d_xz_time_count(av) = do2d_xz_time_count(av) + 1
790                         do2d_xz_last_time(av)  = simulated_time
791                         IF ( .NOT. data_output_2d_on_each_pe  .AND. &
792                              netcdf_output )  THEN
793#if defined( __netcdf )
794                            nc_stat = NF90_PUT_VAR( id_set_xz(av),             &
795                                                    id_var_time_xz(av),        &
796                                             (/ time_since_reference_point /), &
797                                         start = (/ do2d_xz_time_count(av) /), &
798                                                    count = (/ 1 /) )
799                             CALL handle_netcdf_error( 'data_output_2d', 56 )
800#endif
801                         ENDIF
802                      ENDIF
803                   ENDIF
804!
805!--                If required, carry out averaging along y
806                   IF ( section(is,s) == -1 )  THEN
807
808                      ALLOCATE( local_2d_l(nxl-1:nxr+1,nzb:nzt+1) )
809                      local_2d_l = 0.0
810                      ngp = ( nxr-nxl+3 ) * ( nzt-nzb+2 )
811!
812!--                   First local averaging on the PE
813                      DO  k = nzb, nzt+1
814                         DO  j = nys, nyn
815                            DO  i = nxl-1, nxr+1
816                               local_2d_l(i,k) = local_2d_l(i,k) + &
817                                                 local_pf(i,j,k)
818                            ENDDO
819                         ENDDO
820                      ENDDO
821#if defined( __parallel )
822!
823!--                   Now do the averaging over all PEs along y
824                      CALL MPI_ALLREDUCE( local_2d_l(nxl-1,nzb),              &
825                                          local_2d(nxl-1,nzb), ngp, MPI_REAL, &
826                                          MPI_SUM, comm1dy, ierr )
827#else
828                      local_2d = local_2d_l
829#endif
830                      local_2d = local_2d / ( ny + 1.0 )
831
832                      DEALLOCATE( local_2d_l )
833
834                   ELSE
835!
836!--                   Just store the respective section on the local array
837!--                   (but only if it is available on this PE!)
838                      IF ( section(is,s) >= nys  .AND.  section(is,s) <= nyn ) &
839                      THEN
840                         local_2d = local_pf(:,section(is,s),nzb:nzt+1)
841                      ENDIF
842
843                   ENDIF
844
845#if defined( __parallel )
846                   IF ( data_output_2d_on_each_pe )  THEN
847!
848!--                   Output of partial arrays on each PE. If the cross section
849!--                   does not reside on the PE, output special index values.
850#if defined( __netcdf )
851                      IF ( netcdf_output  .AND.  myid == 0 )  THEN
852                         WRITE ( 22 )  simulated_time, do2d_xz_time_count(av), &
853                                       av
854                      ENDIF
855#endif
856                      IF ( ( section(is,s)>=nys .AND. section(is,s)<=nyn ) .OR.&
857                           ( section(is,s) == -1  .AND.  nys-1 == -1 ) )       &
858                      THEN
859                         WRITE (22)  nxl-1, nxr+1, nzb, nzt+1
860                         WRITE (22)  local_2d
861                      ELSE
862                         WRITE (22)  -1, -1, -1, -1
863                      ENDIF
864
865                   ELSE
866!
867!--                   PE0 receives partial arrays from all processors of the
868!--                   respective cross section and outputs them. Here a
869!--                   barrier has to be set, because otherwise
870!--                   "-MPI- FATAL: Remote protocol queue full" may occur.
871                      CALL MPI_BARRIER( comm2d, ierr )
872
873                      ngp = ( nxr-nxl+3 ) * ( nzt-nzb+2 )
874                      IF ( myid == 0 )  THEN
875!
876!--                      Local array can be relocated directly.
877                         IF ( ( section(is,s)>=nys .AND. section(is,s)<=nyn )  &
878                            .OR. ( section(is,s) == -1  .AND.  nys-1 == -1 ) ) &
879                         THEN
880                            total_2d(nxl-1:nxr+1,nzb:nzt+1) = local_2d
881                         ENDIF
882!
883!--                      Receive data from all other PEs.
884                         DO  n = 1, numprocs-1
885!
886!--                         Receive index limits first, then array.
887!--                         Index limits are received in arbitrary order from
888!--                         the PEs.
889                            CALL MPI_RECV( ind(1), 4, MPI_INTEGER,            &
890                                           MPI_ANY_SOURCE, 0, comm2d, status, &
891                                           ierr )
892!
893!--                         Not all PEs have data for XZ-cross-section.
894                            IF ( ind(1) /= -9999 )  THEN
895                               sender = status(MPI_SOURCE)
896                               DEALLOCATE( local_2d )
897                               ALLOCATE( local_2d(ind(1):ind(2),ind(3):ind(4)) )
898                               CALL MPI_RECV( local_2d(ind(1),ind(3)), ngp, &
899                                              MPI_REAL, sender, 1, comm2d,  &
900                                              status, ierr )
901                               total_2d(ind(1):ind(2),ind(3):ind(4)) = local_2d
902                            ENDIF
903                         ENDDO
904!
905!--                      Output of the total cross-section.
906                         IF ( iso2d_output )  THEN
907                            WRITE (22)  total_2d(0:nx+1,nzb:nzt+1)
908                         ENDIF
909!
910!--                      Relocate the local array for the next loop increment
911                         DEALLOCATE( local_2d )
912                         ALLOCATE( local_2d(nxl-1:nxr+1,nzb:nzt+1) )
913
914#if defined( __netcdf )
915                         IF ( netcdf_output )  THEN
916                            nc_stat = NF90_PUT_VAR( id_set_xz(av),             &
917                                                    id_var_do2d(av,if),        &
918                                                    total_2d(0:nx+1,nzb:nzt+1),&
919                               start = (/ 1, is, 1, do2d_xz_time_count(av) /), &
920                                                count = (/ nx+2, 1, nz+2, 1 /) )
921                            CALL handle_netcdf_error( 'data_output_2d', 57 )
922                         ENDIF
923#endif
924
925                      ELSE
926!
927!--                      If the cross section resides on the PE, send the
928!--                      local index limits, otherwise send -9999 to PE0.
929                         IF ( ( section(is,s)>=nys .AND. section(is,s)<=nyn )  &
930                            .OR. ( section(is,s) == -1  .AND.  nys-1 == -1 ) ) &
931                         THEN
932                            ind(1) = nxl-1; ind(2) = nxr+1
933                            ind(3) = nzb;   ind(4) = nzt+1
934                         ELSE
935                            ind(1) = -9999; ind(2) = -9999
936                            ind(3) = -9999; ind(4) = -9999
937                         ENDIF
938                         CALL MPI_SEND( ind(1), 4, MPI_INTEGER, 0, 0, comm2d, &
939                                        ierr )
940!
941!--                      If applicable, send data to PE0.
942                         IF ( ind(1) /= -9999 )  THEN
943                            CALL MPI_SEND( local_2d(nxl-1,nzb), ngp, MPI_REAL, &
944                                           0, 1, comm2d, ierr )
945                         ENDIF
946                      ENDIF
947!
948!--                   A barrier has to be set, because otherwise some PEs may
949!--                   proceed too fast so that PE0 may receive wrong data on
950!--                   tag 0
951                      CALL MPI_BARRIER( comm2d, ierr )
952                   ENDIF
953#else
954                   IF ( iso2d_output )  THEN
955                      WRITE (22)  local_2d(nxl:nxr+1,nzb:nzt+1)
956                   ENDIF
957#if defined( __netcdf )
958                   IF ( netcdf_output )  THEN
959                      nc_stat = NF90_PUT_VAR( id_set_xz(av),                   &
960                                              id_var_do2d(av,if),              &
961                                              local_2d(nxl:nxr+1,nzb:nzt+1),   &
962                               start = (/ 1, is, 1, do2d_xz_time_count(av) /), &
963                                              count = (/ nx+2, 1, nz+2, 1 /) )
964                      CALL handle_netcdf_error( 'data_output_2d', 58 )
965                   ENDIF
966#endif
967#endif
968                   do2d_xz_n = do2d_xz_n + 1
969!
970!--                Write LOCAL-parameter set for ISO2D.
971                   IF ( myid == 0  .AND.  iso2d_output )  THEN
972                      IF ( section(is,s) /= -1 )  THEN
973                         WRITE ( section_chr, '(''y = '',F8.2,'' m  (GP '',I3, &
974                                               &'')'')'                        &
975                               )  section(is,s)*dy, section(is,s)
976                      ELSE
977                         section_chr = 'averaged along y'
978                      ENDIF
979                      IF ( av == 0 )  THEN
980                         rtext = TRIM( do2d(av,if) ) // '  t = ' //    &
981                                 TRIM( simulated_time_chr ) // '  ' // &
982                                 TRIM( section_chr )
983                      ELSE
984                         rtext = TRIM( do2d(av,if) ) // '  averaged t = ' // &
985                                 TRIM( simulated_time_chr ) // '  ' //       &
986                                 TRIM( section_chr )
987                      ENDIF
988                      WRITE (28,LOCAL)
989                   ENDIF
990
991                CASE ( 'yz' )
992!
993!--                Update the NetCDF xy cross section time axis
994                   IF ( myid == 0 )  THEN
995                      IF ( simulated_time /= do2d_yz_last_time(av) )  THEN
996                         do2d_yz_time_count(av) = do2d_yz_time_count(av) + 1
997                         do2d_yz_last_time(av)  = simulated_time
998                         IF ( .NOT. data_output_2d_on_each_pe  .AND. &
999                              netcdf_output )  THEN
1000#if defined( __netcdf )
1001                            nc_stat = NF90_PUT_VAR( id_set_yz(av),             &
1002                                                    id_var_time_yz(av),        &
1003                                             (/ time_since_reference_point /), &
1004                                         start = (/ do2d_yz_time_count(av) /), &
1005                                                    count = (/ 1 /) )
1006                            CALL handle_netcdf_error( 'data_output_2d', 59 )
1007#endif
1008                         ENDIF
1009                      ENDIF
1010                   ENDIF
1011!
1012!--                If required, carry out averaging along x
1013                   IF ( section(is,s) == -1 )  THEN
1014
1015                      ALLOCATE( local_2d_l(nys-1:nyn+1,nzb:nzt+1) )
1016                      local_2d_l = 0.0
1017                      ngp = ( nyn-nys+3 ) * ( nzt-nzb+2 )
1018!
1019!--                   First local averaging on the PE
1020                      DO  k = nzb, nzt+1
1021                         DO  j = nys-1, nyn+1
1022                            DO  i = nxl, nxr
1023                               local_2d_l(j,k) = local_2d_l(j,k) + &
1024                                                 local_pf(i,j,k)
1025                            ENDDO
1026                         ENDDO
1027                      ENDDO
1028#if defined( __parallel )
1029!
1030!--                   Now do the averaging over all PEs along x
1031                      CALL MPI_ALLREDUCE( local_2d_l(nys-1,nzb),              &
1032                                          local_2d(nys-1,nzb), ngp, MPI_REAL, &
1033                                          MPI_SUM, comm1dx, ierr )
1034#else
1035                      local_2d = local_2d_l
1036#endif
1037                      local_2d = local_2d / ( nx + 1.0 )
1038
1039                      DEALLOCATE( local_2d_l )
1040
1041                   ELSE
1042!
1043!--                   Just store the respective section on the local array
1044!--                   (but only if it is available on this PE!)
1045                      IF ( section(is,s) >= nxl  .AND.  section(is,s) <= nxr ) &
1046                      THEN
1047                         local_2d = local_pf(section(is,s),:,nzb:nzt+1)
1048                      ENDIF
1049
1050                   ENDIF
1051
1052#if defined( __parallel )
1053                   IF ( data_output_2d_on_each_pe )  THEN
1054!
1055!--                   Output of partial arrays on each PE. If the cross section
1056!--                   does not reside on the PE, output special index values.
1057#if defined( __netcdf )
1058                      IF ( netcdf_output  .AND.  myid == 0 )  THEN
1059                         WRITE ( 23 )  simulated_time, do2d_yz_time_count(av), &
1060                                       av
1061                      ENDIF
1062#endif
1063                      IF ( ( section(is,s)>=nxl .AND. section(is,s)<=nxr ) .OR.&
1064                           ( section(is,s) ==  -1  .AND.  nxl-1 == -1 ) )      &
1065                      THEN
1066                         WRITE (23)  nys-1, nyn+1, nzb, nzt+1
1067                         WRITE (23)  local_2d
1068                      ELSE
1069                         WRITE (23)  -1, -1, -1, -1
1070                      ENDIF
1071
1072                   ELSE
1073!
1074!--                   PE0 receives partial arrays from all processors of the
1075!--                   respective cross section and outputs them. Here a
1076!--                   barrier has to be set, because otherwise
1077!--                   "-MPI- FATAL: Remote protocol queue full" may occur.
1078                      CALL MPI_BARRIER( comm2d, ierr )
1079
1080                      ngp = ( nyn-nys+3 ) * ( nzt-nzb+2 )
1081                      IF ( myid == 0 )  THEN
1082!
1083!--                      Local array can be relocated directly.
1084                         IF ( ( section(is,s)>=nxl .AND. section(is,s)<=nxr )  &
1085                           .OR. ( section(is,s) ==  -1  .AND.  nxl-1 == -1 ) ) &
1086                         THEN
1087                            total_2d(nys-1:nyn+1,nzb:nzt+1) = local_2d
1088                         ENDIF
1089!
1090!--                      Receive data from all other PEs.
1091                         DO  n = 1, numprocs-1
1092!
1093!--                         Receive index limits first, then array.
1094!--                         Index limits are received in arbitrary order from
1095!--                         the PEs.
1096                            CALL MPI_RECV( ind(1), 4, MPI_INTEGER,            &
1097                                           MPI_ANY_SOURCE, 0, comm2d, status, &
1098                                           ierr )
1099!
1100!--                         Not all PEs have data for YZ-cross-section.
1101                            IF ( ind(1) /= -9999 )  THEN
1102                               sender = status(MPI_SOURCE)
1103                               DEALLOCATE( local_2d )
1104                               ALLOCATE( local_2d(ind(1):ind(2),ind(3):ind(4)) )
1105                               CALL MPI_RECV( local_2d(ind(1),ind(3)), ngp, &
1106                                              MPI_REAL, sender, 1, comm2d,  &
1107                                              status, ierr )
1108                               total_2d(ind(1):ind(2),ind(3):ind(4)) = local_2d
1109                            ENDIF
1110                         ENDDO
1111!
1112!--                      Output of the total cross-section.
1113                         IF ( iso2d_output )  THEN
1114                            WRITE (23)  total_2d(0:ny+1,nzb:nzt+1)
1115                         ENDIF
1116!
1117!--                      Relocate the local array for the next loop increment
1118                         DEALLOCATE( local_2d )
1119                         ALLOCATE( local_2d(nys-1:nyn+1,nzb:nzt+1) )
1120
1121#if defined( __netcdf )
1122                         IF ( netcdf_output )  THEN
1123                            nc_stat = NF90_PUT_VAR( id_set_yz(av),             &
1124                                                    id_var_do2d(av,if),        &
1125                                                    total_2d(0:ny+1,nzb:nzt+1),&
1126                               start = (/ is, 1, 1, do2d_yz_time_count(av) /), &
1127                                                count = (/ 1, ny+2, nz+2, 1 /) )
1128                            CALL handle_netcdf_error( 'data_output_2d', 60 )
1129                         ENDIF
1130#endif
1131
1132                      ELSE
1133!
1134!--                      If the cross section resides on the PE, send the
1135!--                      local index limits, otherwise send -9999 to PE0.
1136                         IF ( ( section(is,s)>=nxl .AND. section(is,s)<=nxr )  &
1137                           .OR. ( section(is,s) ==  -1  .AND.  nxl-1 == -1 ) ) &
1138                         THEN
1139                            ind(1) = nys-1; ind(2) = nyn+1
1140                            ind(3) = nzb;   ind(4) = nzt+1
1141                         ELSE
1142                            ind(1) = -9999; ind(2) = -9999
1143                            ind(3) = -9999; ind(4) = -9999
1144                         ENDIF
1145                         CALL MPI_SEND( ind(1), 4, MPI_INTEGER, 0, 0, comm2d, &
1146                                        ierr )
1147!
1148!--                      If applicable, send data to PE0.
1149                         IF ( ind(1) /= -9999 )  THEN
1150                            CALL MPI_SEND( local_2d(nys-1,nzb), ngp, MPI_REAL, &
1151                                           0, 1, comm2d, ierr )
1152                         ENDIF
1153                      ENDIF
1154!
1155!--                   A barrier has to be set, because otherwise some PEs may
1156!--                   proceed too fast so that PE0 may receive wrong data on
1157!--                   tag 0
1158                      CALL MPI_BARRIER( comm2d, ierr )
1159                   ENDIF
1160#else
1161                   IF ( iso2d_output )  THEN
1162                      WRITE (23)  local_2d(nys:nyn+1,nzb:nzt+1)
1163                   ENDIF
1164#if defined( __netcdf )
1165                   IF ( netcdf_output )  THEN
1166                      nc_stat = NF90_PUT_VAR( id_set_yz(av),                   &
1167                                              id_var_do2d(av,if),              &
1168                                              local_2d(nys:nyn+1,nzb:nzt+1),   &
1169                               start = (/ is, 1, 1, do2d_xz_time_count(av) /), &
1170                                              count = (/ 1, ny+2, nz+2, 1 /) )
1171                      CALL handle_netcdf_error( 'data_output_2d', 61 )
1172                   ENDIF
1173#endif
1174#endif
1175                   do2d_yz_n = do2d_yz_n + 1
1176!
1177!--                Write LOCAL-parameter set for ISO2D.
1178                   IF ( myid == 0  .AND.  iso2d_output )  THEN
1179                      IF ( section(is,s) /= -1 )  THEN
1180                         WRITE ( section_chr, '(''x = '',F8.2,'' m  (GP '',I3, &
1181                                               &'')'')'                        &
1182                               )  section(is,s)*dx, section(is,s)
1183                      ELSE
1184                         section_chr = 'averaged along x'
1185                      ENDIF
1186                      IF ( av == 0 )  THEN
1187                         rtext = TRIM( do2d(av,if) ) // '  t = ' //    &
1188                                 TRIM( simulated_time_chr ) // '  ' // &
1189                                 TRIM( section_chr )
1190                      ELSE
1191                         rtext = TRIM( do2d(av,if) ) // '  averaged t = ' // &
1192                                 TRIM( simulated_time_chr ) // '  ' //       &
1193                                 TRIM( section_chr )
1194                      ENDIF
1195                      WRITE (29,LOCAL)
1196                   ENDIF
1197
1198             END SELECT
1199
1200             is = is + 1
1201          ENDDO loop1
1202
1203       ENDIF
1204
1205       if = if + 1
1206       l = MAX( 2, LEN_TRIM( do2d(av,if) ) )
1207       do2d_mode = do2d(av,if)(l-1:l)
1208
1209    ENDDO
1210
1211!
1212!-- Deallocate temporary arrays.
1213    IF ( ALLOCATED( level_z ) )  DEALLOCATE( level_z )
1214    DEALLOCATE( local_pf, local_2d )
1215#if defined( __parallel )
1216    IF ( .NOT.  data_output_2d_on_each_pe  .AND.  myid == 0 )  THEN
1217       DEALLOCATE( total_2d )
1218    ENDIF
1219#endif
1220
1221!
1222!-- Close plot output file.
1223    file_id = 20 + s
1224
1225    IF ( data_output_2d_on_each_pe )  THEN
1226       CALL close_file( file_id )
1227    ELSE
1228       IF ( myid == 0 )  CALL close_file( file_id )
1229    ENDIF
1230
1231
1232    CALL cpu_log (log_point(3),'data_output_2d','stop','nobarrier')
1233
1234 END SUBROUTINE data_output_2d
Note: See TracBrowser for help on using the repository browser.