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

Last change on this file since 4444 was 4444, checked in by raasch, 4 years ago

bugfix: cpp-directives for serial mode added

  • Property svn:keywords set to Id
File size: 88.8 KB
Line 
1!> @file data_output_2d.f90
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2020 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! ------------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: data_output_2d.f90 4444 2020-03-05 15:59:50Z raasch $
27! bugfix: cpp-directives for serial mode added
28!
29! 4442 2020-03-04 19:21:13Z suehring
30! Change order of dimension in surface array %frac to allow for better
31! vectorization.
32!
33! 4441 2020-03-04 19:20:35Z suehring
34! Introduction of wall_flags_total_0, which currently sets bits based on static
35! topography information used in wall_flags_static_0
36!
37! 4331 2019-12-10 18:25:02Z suehring
38! Move 2-m potential temperature output to diagnostic_output_quantities
39!
40! 4329 2019-12-10 15:46:36Z motisi
41! Renamed wall_flags_0 to wall_flags_static_0
42!
43! 4182 2019-08-22 15:20:23Z scharf
44! Corrected "Former revisions" section
45!
46! 4048 2019-06-21 21:00:21Z knoop
47! Removed turbulence_closure_mod dependency
48!
49! 4039 2019-06-18 10:32:41Z suehring
50! modularize diagnostic output
51!
52! 3994 2019-05-22 18:08:09Z suehring
53! output of turbulence intensity added
54!
55! 3987 2019-05-22 09:52:13Z kanani
56! Introduce alternative switch for debug output during timestepping
57!
58! 3943 2019-05-02 09:50:41Z maronga
59! Added output of qsws for green roofs.
60!
61! 3885 2019-04-11 11:29:34Z kanani
62! Changes related to global restructuring of location messages and introduction
63! of additional debug messages
64!
65! 3766 2019-02-26 16:23:41Z raasch
66! unused variables removed
67!
68! 3655 2019-01-07 16:51:22Z knoop
69! Bugfix: use time_since_reference_point instead of simulated_time (relevant
70! when using wall/soil spinup)
71!
72! Revision 1.1  1997/08/11 06:24:09  raasch
73! Initial revision
74!
75!
76! Description:
77! ------------
78!> Data output of cross-sections in netCDF format or binary format
79!> to be later converted to NetCDF by helper routine combine_plot_fields.
80!> Attention: The position of the sectional planes is still not always computed
81!> ---------  correctly. (zu is used always)!
82!------------------------------------------------------------------------------!
83 SUBROUTINE data_output_2d( mode, av )
84 
85
86    USE arrays_3d,                                                                                 &
87        ONLY:  dzw, d_exner, e, heatflux_output_conversion, p, pt, q, ql, ql_c, ql_v, s, tend, u,  &
88               v, vpt, w, waterflux_output_conversion, zu, zw
89
90    USE averaging
91
92    USE basic_constants_and_equations_mod,                                     &
93        ONLY:  c_p, lv_d_cp, l_v
94
95    USE bulk_cloud_model_mod,                                                  &
96        ONLY:  bulk_cloud_model
97
98    USE control_parameters,                                                    &
99        ONLY:  data_output_2d_on_each_pe,                                      &
100               data_output_xy, data_output_xz, data_output_yz,                 &
101               debug_output_timestep,                                          &
102               do2d,                                                           &
103               do2d_xy_last_time, do2d_xy_time_count,                          &
104               do2d_xz_last_time, do2d_xz_time_count,                          &
105               do2d_yz_last_time, do2d_yz_time_count,                          &
106               ibc_uv_b, io_blocks, io_group, message_string,                  &
107               ntdim_2d_xy, ntdim_2d_xz, ntdim_2d_yz,                          &
108               psolver, section,                                               &
109               time_since_reference_point
110
111    USE cpulog,                                                                &
112        ONLY:  cpu_log, log_point
113
114    USE indices,                                                               &
115        ONLY:  nbgp, nx, nxl, nxlg, nxr, nxrg, ny, nyn, nyng, nys, nysg,       &
116               nzb, nzt, wall_flags_total_0
117
118    USE kinds
119
120    USE land_surface_model_mod,                                                &
121        ONLY:  zs
122
123    USE module_interface,                                                      &
124        ONLY:  module_interface_data_output_2d
125
126#if defined( __netcdf )
127    USE NETCDF
128#endif
129
130    USE netcdf_interface,                                                      &
131        ONLY:  fill_value, id_set_xy, id_set_xz, id_set_yz, id_var_do2d,       &
132               id_var_time_xy, id_var_time_xz, id_var_time_yz, nc_stat,        &
133               netcdf_data_format, netcdf_handle_error
134
135    USE particle_attributes,                                                   &
136        ONLY:  grid_particles, number_of_particles, particle_advection_start,  &
137               particles, prt_count
138   
139    USE pegrid
140
141    USE surface_mod,                                                           &
142        ONLY:  ind_pav_green, ind_veg_wall, ind_wat_win, surf_def_h,           &
143               surf_lsm_h, surf_usm_h
144
145
146    IMPLICIT NONE
147
148    CHARACTER (LEN=2)  ::  do2d_mode    !< output mode of variable ('xy', 'xz', 'yz')
149    CHARACTER (LEN=2)  ::  mode         !< mode with which the routine is called ('xy', 'xz', 'yz')
150    CHARACTER (LEN=4)  ::  grid         !< string defining the vertical grid
151   
152    INTEGER(iwp) ::  av        !< flag for (non-)average output
153    INTEGER(iwp) ::  ngp       !< number of grid points of an output slice
154    INTEGER(iwp) ::  file_id   !< id of output files
155    INTEGER(iwp) ::  flag_nr   !< number of masking flag
156    INTEGER(iwp) ::  i         !< loop index
157    INTEGER(iwp) ::  is        !< slice index
158    INTEGER(iwp) ::  ivar      !< variable index
159    INTEGER(iwp) ::  j         !< loop index
160    INTEGER(iwp) ::  k         !< loop index
161    INTEGER(iwp) ::  l         !< loop index
162    INTEGER(iwp) ::  layer_xy  !< vertical index of a xy slice in array 'local_pf'
163    INTEGER(iwp) ::  m         !< loop index
164    INTEGER(iwp) ::  n         !< loop index
165    INTEGER(iwp) ::  nis       !< number of vertical slices to be written via parallel NetCDF output
166    INTEGER(iwp) ::  ns        !< number of output slices
167    INTEGER(iwp) ::  nzb_do    !< lower limit of the data field (usually nzb)
168    INTEGER(iwp) ::  nzt_do    !< upper limit of the data field (usually nzt+1)
169    INTEGER(iwp) ::  s_ind     !< index of slice types (xy=1, xz=2, yz=3)
170#if defined( __parallel )
171    INTEGER(iwp) ::  iis       !< vertical index of a xy slice in array 'local_2d_sections'
172    INTEGER(iwp) ::  sender    !< PE id of sending PE
173    INTEGER(iwp) ::  ind(4)    !< index limits (lower/upper bounds) of array 'local_2d'
174#endif
175
176    LOGICAL ::  found          !< true if output variable was found
177    LOGICAL ::  resorted       !< true if variable is resorted
178    LOGICAL ::  two_d          !< true if variable is only two dimensional
179
180    REAL(wp) ::  mean_r        !< mean particle radius
181    REAL(wp) ::  s_r2          !< sum( particle-radius**2 )
182    REAL(wp) ::  s_r3          !< sum( particle-radius**3 )
183   
184    REAL(wp), DIMENSION(:), ALLOCATABLE     ::  level_z             !< z levels for output array
185    REAL(wp), DIMENSION(:,:), ALLOCATABLE   ::  local_2d            !< local 2-dimensional array containing output values
186    REAL(wp), DIMENSION(:,:), ALLOCATABLE   ::  local_2d_l          !< local 2-dimensional array containing output values
187
188    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  local_pf            !< output array
189    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  local_2d_sections   !< local array containing values at all slices
190    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  local_2d_sections_l !< local array containing values at all slices
191
192#if defined( __parallel )
193    REAL(wp), DIMENSION(:,:),   ALLOCATABLE ::  total_2d    !< same as local_2d
194#endif
195    REAL(wp), DIMENSION(:,:,:), POINTER ::  to_be_resorted  !< points to array which shall be output
196
197
198    IF ( debug_output_timestep )  CALL debug_message( 'data_output_2d', 'start' )
199!
200!-- Immediate return, if no output is requested (no respective sections
201!-- found in parameter data_output)
202    IF ( mode == 'xy'  .AND.  .NOT. data_output_xy(av) )  RETURN
203    IF ( mode == 'xz'  .AND.  .NOT. data_output_xz(av) )  RETURN
204    IF ( mode == 'yz'  .AND.  .NOT. data_output_yz(av) )  RETURN
205
206    CALL cpu_log (log_point(3),'data_output_2d','start')
207
208    two_d = .FALSE.    ! local variable to distinguish between output of pure 2D
209                       ! arrays and cross-sections of 3D arrays.
210
211!
212!-- Depending on the orientation of the cross-section, the respective output
213!-- files have to be opened.
214    SELECT CASE ( mode )
215
216       CASE ( 'xy' )
217          s_ind = 1
218          ALLOCATE( level_z(nzb:nzt+1), local_2d(nxl:nxr,nys:nyn) )
219
220          IF ( netcdf_data_format > 4 )  THEN
221             ns = 1
222             DO WHILE ( section(ns,s_ind) /= -9999  .AND.  ns <= 100 )
223                ns = ns + 1
224             ENDDO
225             ns = ns - 1
226             ALLOCATE( local_2d_sections(nxl:nxr,nys:nyn,1:ns) )
227             local_2d_sections = 0.0_wp
228          ENDIF
229
230!
231!--       Parallel netCDF4/HDF5 output is done on all PEs, all other on PE0 only
232          IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
233             CALL check_open( 101+av*10 )
234          ENDIF
235          IF ( data_output_2d_on_each_pe  .AND.  netcdf_data_format < 5 )  THEN
236             CALL check_open( 21 )
237          ELSE
238             IF ( myid == 0 )  THEN
239#if defined( __parallel )
240                ALLOCATE( total_2d(0:nx,0:ny) )
241#endif
242             ENDIF
243          ENDIF
244
245       CASE ( 'xz' )
246          s_ind = 2
247          ALLOCATE( local_2d(nxl:nxr,nzb:nzt+1) )
248
249          IF ( netcdf_data_format > 4 )  THEN
250             ns = 1
251             DO WHILE ( section(ns,s_ind) /= -9999  .AND.  ns <= 100 )
252                ns = ns + 1
253             ENDDO
254             ns = ns - 1
255             ALLOCATE( local_2d_sections(nxl:nxr,1:ns,nzb:nzt+1) )
256             ALLOCATE( local_2d_sections_l(nxl:nxr,1:ns,nzb:nzt+1) )
257             local_2d_sections = 0.0_wp; local_2d_sections_l = 0.0_wp
258          ENDIF
259
260!
261!--       Parallel netCDF4/HDF5 output is done on all PEs, all other on PE0 only
262          IF ( myid == 0 .OR. netcdf_data_format > 4 )  THEN
263             CALL check_open( 102+av*10 )
264          ENDIF
265
266          IF ( data_output_2d_on_each_pe  .AND.  netcdf_data_format < 5 )  THEN
267             CALL check_open( 22 )
268          ELSE
269             IF ( myid == 0 )  THEN
270#if defined( __parallel )
271                ALLOCATE( total_2d(0:nx,nzb:nzt+1) )
272#endif
273             ENDIF
274          ENDIF
275
276       CASE ( 'yz' )
277          s_ind = 3
278          ALLOCATE( local_2d(nys:nyn,nzb:nzt+1) )
279
280          IF ( netcdf_data_format > 4 )  THEN
281             ns = 1
282             DO WHILE ( section(ns,s_ind) /= -9999  .AND.  ns <= 100 )
283                ns = ns + 1
284             ENDDO
285             ns = ns - 1
286             ALLOCATE( local_2d_sections(1:ns,nys:nyn,nzb:nzt+1) )
287             ALLOCATE( local_2d_sections_l(1:ns,nys:nyn,nzb:nzt+1) )
288             local_2d_sections = 0.0_wp; local_2d_sections_l = 0.0_wp
289          ENDIF
290
291!
292!--       Parallel netCDF4/HDF5 output is done on all PEs, all other on PE0 only
293          IF ( myid == 0 .OR. netcdf_data_format > 4 )  THEN
294             CALL check_open( 103+av*10 )
295          ENDIF
296
297          IF ( data_output_2d_on_each_pe  .AND.  netcdf_data_format < 5 )  THEN
298             CALL check_open( 23 )
299          ELSE
300             IF ( myid == 0 )  THEN
301#if defined( __parallel )
302                ALLOCATE( total_2d(0:ny,nzb:nzt+1) )
303#endif
304             ENDIF
305          ENDIF
306
307       CASE DEFAULT
308          message_string = 'unknown cross-section: ' // TRIM( mode )
309          CALL message( 'data_output_2d', 'PA0180', 1, 2, 0, 6, 0 )
310
311    END SELECT
312
313!
314!-- For parallel netcdf output the time axis must be limited. Return, if this
315!-- limit is exceeded. This could be the case, if the simulated time exceeds
316!-- the given end time by the length of the given output interval.
317    IF ( netcdf_data_format > 4 )  THEN
318       IF ( mode == 'xy'  .AND.  do2d_xy_time_count(av) + 1 >                  &
319            ntdim_2d_xy(av) )  THEN
320          WRITE ( message_string, * ) 'Output of xy cross-sections is not ',   &
321                          'given at t=', time_since_reference_point, 's because the',       & 
322                          ' maximum number of output time levels is exceeded.'
323          CALL message( 'data_output_2d', 'PA0384', 0, 1, 0, 6, 0 )
324          CALL cpu_log( log_point(3), 'data_output_2d', 'stop' )
325          RETURN
326       ENDIF
327       IF ( mode == 'xz'  .AND.  do2d_xz_time_count(av) + 1 >                  &
328            ntdim_2d_xz(av) )  THEN
329          WRITE ( message_string, * ) 'Output of xz cross-sections is not ',   &
330                          'given at t=', time_since_reference_point, 's because the',       & 
331                          ' maximum number of output time levels is exceeded.'
332          CALL message( 'data_output_2d', 'PA0385', 0, 1, 0, 6, 0 )
333          CALL cpu_log( log_point(3), 'data_output_2d', 'stop' )
334          RETURN
335       ENDIF
336       IF ( mode == 'yz'  .AND.  do2d_yz_time_count(av) + 1 >                  &
337            ntdim_2d_yz(av) )  THEN
338          WRITE ( message_string, * ) 'Output of yz cross-sections is not ',   &
339                          'given at t=', time_since_reference_point, 's because the',       & 
340                          ' maximum number of output time levels is exceeded.'
341          CALL message( 'data_output_2d', 'PA0386', 0, 1, 0, 6, 0 )
342          CALL cpu_log( log_point(3), 'data_output_2d', 'stop' )
343          RETURN
344       ENDIF
345    ENDIF
346
347!
348!-- Allocate a temporary array for resorting (kji -> ijk).
349    ALLOCATE( local_pf(nxl:nxr,nys:nyn,nzb:nzt+1) )
350    local_pf = 0.0
351
352!
353!-- Loop of all variables to be written.
354!-- Output dimensions chosen
355    ivar = 1
356    l = MAX( 2, LEN_TRIM( do2d(av,ivar) ) )
357    do2d_mode = do2d(av,ivar)(l-1:l)
358
359    DO  WHILE ( do2d(av,ivar)(1:1) /= ' ' )
360
361       IF ( do2d_mode == mode )  THEN
362!
363!--       Set flag to steer output of radiation, land-surface, or user-defined
364!--       quantities
365          found = .FALSE.
366
367          nzb_do = nzb
368          nzt_do = nzt+1
369!
370!--       Before each output, set array local_pf to fill value
371          local_pf = fill_value
372!
373!--       Set masking flag for topography for not resorted arrays
374          flag_nr = 0
375         
376!
377!--       Store the array chosen on the temporary array.
378          resorted = .FALSE.
379          SELECT CASE ( TRIM( do2d(av,ivar) ) )
380             CASE ( 'e_xy', 'e_xz', 'e_yz' )
381                IF ( av == 0 )  THEN
382                   to_be_resorted => e
383                ELSE
384                   IF ( .NOT. ALLOCATED( e_av ) ) THEN
385                      ALLOCATE( e_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
386                      e_av = REAL( fill_value, KIND = wp )
387                   ENDIF
388                   to_be_resorted => e_av
389                ENDIF
390                IF ( mode == 'xy' )  level_z = zu
391
392             CASE ( 'thetal_xy', 'thetal_xz', 'thetal_yz' )
393                IF ( av == 0 )  THEN
394                   to_be_resorted => pt
395                ELSE
396                   IF ( .NOT. ALLOCATED( lpt_av ) ) THEN
397                      ALLOCATE( lpt_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
398                      lpt_av = REAL( fill_value, KIND = wp )
399                   ENDIF
400                   to_be_resorted => lpt_av
401                ENDIF
402                IF ( mode == 'xy' )  level_z = zu
403
404             CASE ( 'lwp*_xy' )        ! 2d-array
405                IF ( av == 0 )  THEN
406                   DO  i = nxl, nxr
407                      DO  j = nys, nyn
408                         local_pf(i,j,nzb+1) = SUM( ql(nzb:nzt,j,i) *          &
409                                                    dzw(1:nzt+1) )
410                      ENDDO
411                   ENDDO
412                ELSE
413                   IF ( .NOT. ALLOCATED( lwp_av ) ) THEN
414                      ALLOCATE( lwp_av(nysg:nyng,nxlg:nxrg) )
415                      lwp_av = REAL( fill_value, KIND = wp )
416                   ENDIF
417                   DO  i = nxl, nxr
418                      DO  j = nys, nyn
419                         local_pf(i,j,nzb+1) = lwp_av(j,i)
420                      ENDDO
421                   ENDDO
422                ENDIF
423                resorted = .TRUE.
424                two_d = .TRUE.
425                level_z(nzb+1) = zu(nzb+1)
426
427             CASE ( 'ghf*_xy' )        ! 2d-array
428                IF ( av == 0 )  THEN
429                   DO  m = 1, surf_lsm_h%ns
430                      i                   = surf_lsm_h%i(m)           
431                      j                   = surf_lsm_h%j(m)
432                      local_pf(i,j,nzb+1) = surf_lsm_h%ghf(m)
433                   ENDDO
434                   DO  m = 1, surf_usm_h%ns
435                      i                   = surf_usm_h%i(m)           
436                      j                   = surf_usm_h%j(m)
437                      local_pf(i,j,nzb+1) = surf_usm_h%frac(m,ind_veg_wall)  *  &
438                                            surf_usm_h%wghf_eb(m)        +      &
439                                            surf_usm_h%frac(m,ind_pav_green) *  &
440                                            surf_usm_h%wghf_eb_green(m)  +      &
441                                            surf_usm_h%frac(m,ind_wat_win)   *  &
442                                            surf_usm_h%wghf_eb_window(m)
443                   ENDDO
444                ELSE
445                   IF ( .NOT. ALLOCATED( ghf_av ) ) THEN
446                      ALLOCATE( ghf_av(nysg:nyng,nxlg:nxrg) )
447                      ghf_av = REAL( fill_value, KIND = wp )
448                   ENDIF
449                   DO  i = nxl, nxr
450                      DO  j = nys, nyn
451                         local_pf(i,j,nzb+1) = ghf_av(j,i)
452                      ENDDO
453                   ENDDO
454                ENDIF
455
456                resorted = .TRUE.
457                two_d = .TRUE.
458                level_z(nzb+1) = zu(nzb+1)
459
460             CASE ( 'ol*_xy' )        ! 2d-array
461                IF ( av == 0 ) THEN
462                   DO  m = 1, surf_def_h(0)%ns
463                      i = surf_def_h(0)%i(m)
464                      j = surf_def_h(0)%j(m)
465                      local_pf(i,j,nzb+1) = surf_def_h(0)%ol(m)
466                   ENDDO
467                   DO  m = 1, surf_lsm_h%ns
468                      i = surf_lsm_h%i(m)
469                      j = surf_lsm_h%j(m)
470                      local_pf(i,j,nzb+1) = surf_lsm_h%ol(m)
471                   ENDDO
472                   DO  m = 1, surf_usm_h%ns
473                      i = surf_usm_h%i(m)
474                      j = surf_usm_h%j(m)
475                      local_pf(i,j,nzb+1) = surf_usm_h%ol(m)
476                   ENDDO
477                ELSE
478                   IF ( .NOT. ALLOCATED( ol_av ) ) THEN
479                      ALLOCATE( ol_av(nysg:nyng,nxlg:nxrg) )
480                      ol_av = REAL( fill_value, KIND = wp )
481                   ENDIF
482                   DO  i = nxl, nxr
483                      DO  j = nys, nyn
484                         local_pf(i,j,nzb+1) = ol_av(j,i)
485                      ENDDO
486                   ENDDO
487                ENDIF
488                resorted = .TRUE.
489                two_d = .TRUE.
490                level_z(nzb+1) = zu(nzb+1)
491
492             CASE ( 'p_xy', 'p_xz', 'p_yz' )
493                IF ( av == 0 )  THEN
494                   IF ( psolver /= 'sor' )  CALL exchange_horiz( p, nbgp )
495                   to_be_resorted => p
496                ELSE
497                   IF ( .NOT. ALLOCATED( p_av ) ) THEN
498                      ALLOCATE( p_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
499                      p_av = REAL( fill_value, KIND = wp )
500                   ENDIF
501                   IF ( psolver /= 'sor' )  CALL exchange_horiz( p_av, nbgp )
502                   to_be_resorted => p_av
503                ENDIF
504                IF ( mode == 'xy' )  level_z = zu
505
506             CASE ( 'pc_xy', 'pc_xz', 'pc_yz' )  ! particle concentration
507                IF ( av == 0 )  THEN
508                   IF ( time_since_reference_point >= particle_advection_start )  THEN
509                      tend = prt_count
510!                      CALL exchange_horiz( tend, nbgp )
511                   ELSE
512                      tend = 0.0_wp
513                   ENDIF
514                   DO  i = nxl, nxr
515                      DO  j = nys, nyn
516                         DO  k = nzb, nzt+1
517                            local_pf(i,j,k) = tend(k,j,i)
518                         ENDDO
519                      ENDDO
520                   ENDDO
521                   resorted = .TRUE.
522                ELSE
523                   IF ( .NOT. ALLOCATED( pc_av ) ) THEN
524                      ALLOCATE( pc_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
525                      pc_av = REAL( fill_value, KIND = wp )
526                   ENDIF
527!                   CALL exchange_horiz( pc_av, nbgp )
528                   to_be_resorted => pc_av
529                ENDIF
530
531             CASE ( 'pr_xy', 'pr_xz', 'pr_yz' )  ! mean particle radius (effective radius)
532                IF ( av == 0 )  THEN
533                   IF ( time_since_reference_point >= particle_advection_start )  THEN
534                      DO  i = nxl, nxr
535                         DO  j = nys, nyn
536                            DO  k = nzb, nzt+1
537                               number_of_particles = prt_count(k,j,i)
538                               IF (number_of_particles <= 0)  CYCLE
539                               particles => grid_particles(k,j,i)%particles(1:number_of_particles)
540                               s_r2 = 0.0_wp
541                               s_r3 = 0.0_wp
542                               DO  n = 1, number_of_particles
543                                  IF ( particles(n)%particle_mask )  THEN
544                                     s_r2 = s_r2 + particles(n)%radius**2 * &
545                                            particles(n)%weight_factor
546                                     s_r3 = s_r3 + particles(n)%radius**3 * &
547                                            particles(n)%weight_factor
548                                  ENDIF
549                               ENDDO
550                               IF ( s_r2 > 0.0_wp )  THEN
551                                  mean_r = s_r3 / s_r2
552                               ELSE
553                                  mean_r = 0.0_wp
554                               ENDIF
555                               tend(k,j,i) = mean_r
556                            ENDDO
557                         ENDDO
558                      ENDDO
559!                      CALL exchange_horiz( tend, nbgp )
560                   ELSE
561                      tend = 0.0_wp
562                   ENDIF
563                   DO  i = nxl, nxr
564                      DO  j = nys, nyn
565                         DO  k = nzb, nzt+1
566                            local_pf(i,j,k) = tend(k,j,i)
567                         ENDDO
568                      ENDDO
569                   ENDDO
570                   resorted = .TRUE.
571                ELSE
572                   IF ( .NOT. ALLOCATED( pr_av ) ) THEN
573                      ALLOCATE( pr_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
574                      pr_av = REAL( fill_value, KIND = wp )
575                   ENDIF
576!                   CALL exchange_horiz( pr_av, nbgp )
577                   to_be_resorted => pr_av
578                ENDIF
579
580             CASE ( 'theta_xy', 'theta_xz', 'theta_yz' )
581                IF ( av == 0 )  THEN
582                   IF ( .NOT. bulk_cloud_model ) THEN
583                      to_be_resorted => pt
584                   ELSE
585                   DO  i = nxl, nxr
586                      DO  j = nys, nyn
587                            DO  k = nzb, nzt+1
588                               local_pf(i,j,k) = pt(k,j,i) + lv_d_cp *         &
589                                                             d_exner(k) *      &
590                                                             ql(k,j,i)
591                            ENDDO
592                         ENDDO
593                      ENDDO
594                      resorted = .TRUE.
595                   ENDIF
596                ELSE
597                   IF ( .NOT. ALLOCATED( pt_av ) ) THEN
598                      ALLOCATE( pt_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
599                      pt_av = REAL( fill_value, KIND = wp )
600                   ENDIF
601                   to_be_resorted => pt_av
602                ENDIF
603                IF ( mode == 'xy' )  level_z = zu
604
605             CASE ( 'q_xy', 'q_xz', 'q_yz' )
606                IF ( av == 0 )  THEN
607                   to_be_resorted => q
608                ELSE
609                   IF ( .NOT. ALLOCATED( q_av ) ) THEN
610                      ALLOCATE( q_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
611                      q_av = REAL( fill_value, KIND = wp )
612                   ENDIF
613                   to_be_resorted => q_av
614                ENDIF
615                IF ( mode == 'xy' )  level_z = zu
616
617             CASE ( 'ql_xy', 'ql_xz', 'ql_yz' )
618                IF ( av == 0 )  THEN
619                   to_be_resorted => ql
620                ELSE
621                   IF ( .NOT. ALLOCATED( ql_av ) ) THEN
622                      ALLOCATE( ql_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
623                      ql_av = REAL( fill_value, KIND = wp )
624                   ENDIF
625                   to_be_resorted => ql_av
626                ENDIF
627                IF ( mode == 'xy' )  level_z = zu
628
629             CASE ( 'ql_c_xy', 'ql_c_xz', 'ql_c_yz' )
630                IF ( av == 0 )  THEN
631                   to_be_resorted => ql_c
632                ELSE
633                   IF ( .NOT. ALLOCATED( ql_c_av ) ) THEN
634                      ALLOCATE( ql_c_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
635                      ql_c_av = REAL( fill_value, KIND = wp )
636                   ENDIF
637                   to_be_resorted => ql_c_av
638                ENDIF
639                IF ( mode == 'xy' )  level_z = zu
640
641             CASE ( 'ql_v_xy', 'ql_v_xz', 'ql_v_yz' )
642                IF ( av == 0 )  THEN
643                   to_be_resorted => ql_v
644                ELSE
645                   IF ( .NOT. ALLOCATED( ql_v_av ) ) THEN
646                      ALLOCATE( ql_v_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
647                      ql_v_av = REAL( fill_value, KIND = wp )
648                   ENDIF
649                   to_be_resorted => ql_v_av
650                ENDIF
651                IF ( mode == 'xy' )  level_z = zu
652
653             CASE ( 'ql_vp_xy', 'ql_vp_xz', 'ql_vp_yz' )
654                IF ( av == 0 )  THEN
655                   IF ( time_since_reference_point >= particle_advection_start )  THEN
656                      DO  i = nxl, nxr
657                         DO  j = nys, nyn
658                            DO  k = nzb, nzt+1
659                               number_of_particles = prt_count(k,j,i)
660                               IF (number_of_particles <= 0)  CYCLE
661                               particles => grid_particles(k,j,i)%particles(1:number_of_particles)
662                               DO  n = 1, number_of_particles
663                                  IF ( particles(n)%particle_mask )  THEN
664                                     tend(k,j,i) =  tend(k,j,i) +                 &
665                                                    particles(n)%weight_factor /  &
666                                                    prt_count(k,j,i)
667                                  ENDIF
668                               ENDDO
669                            ENDDO
670                         ENDDO
671                      ENDDO
672!                      CALL exchange_horiz( tend, nbgp )
673                   ELSE
674                      tend = 0.0_wp
675                   ENDIF
676                   DO  i = nxl, nxr
677                      DO  j = nys, nyn
678                         DO  k = nzb, nzt+1
679                            local_pf(i,j,k) = tend(k,j,i)
680                         ENDDO
681                      ENDDO
682                   ENDDO
683                   resorted = .TRUE.
684                ELSE
685                   IF ( .NOT. ALLOCATED( ql_vp_av ) ) THEN
686                      ALLOCATE( ql_vp_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
687                      ql_vp_av = REAL( fill_value, KIND = wp )
688                   ENDIF
689!                   CALL exchange_horiz( ql_vp_av, nbgp )
690                   to_be_resorted => ql_vp_av
691                ENDIF
692                IF ( mode == 'xy' )  level_z = zu
693
694             CASE ( 'qsws*_xy' )        ! 2d-array
695                IF ( av == 0 ) THEN
696                   local_pf(:,:,nzb+1) = REAL( fill_value, KIND = wp )
697!
698!--                In case of default surfaces, clean-up flux by density.
699!--                In case of land-surfaces, convert fluxes into
700!--                dynamic units
701                   DO  m = 1, surf_def_h(0)%ns
702                      i = surf_def_h(0)%i(m)
703                      j = surf_def_h(0)%j(m)
704                      k = surf_def_h(0)%k(m)
705                      local_pf(i,j,nzb+1) = surf_def_h(0)%qsws(m) *            &
706                                            waterflux_output_conversion(k)
707                   ENDDO
708                   DO  m = 1, surf_lsm_h%ns
709                      i = surf_lsm_h%i(m)
710                      j = surf_lsm_h%j(m)
711                      k = surf_lsm_h%k(m)
712                      local_pf(i,j,nzb+1) = surf_lsm_h%qsws(m) * l_v
713                   ENDDO
714                   DO  m = 1, surf_usm_h%ns
715                      i = surf_usm_h%i(m)
716                      j = surf_usm_h%j(m)
717                      k = surf_usm_h%k(m)
718                      local_pf(i,j,nzb+1) = surf_usm_h%qsws(m) * l_v
719                   ENDDO
720                ELSE
721                   IF ( .NOT. ALLOCATED( qsws_av ) ) THEN
722                      ALLOCATE( qsws_av(nysg:nyng,nxlg:nxrg) )
723                      qsws_av = REAL( fill_value, KIND = wp )
724                   ENDIF
725                   DO  i = nxl, nxr
726                      DO  j = nys, nyn 
727                         local_pf(i,j,nzb+1) =  qsws_av(j,i)
728                      ENDDO
729                   ENDDO
730                ENDIF
731                resorted = .TRUE.
732                two_d = .TRUE.
733                level_z(nzb+1) = zu(nzb+1)
734
735             CASE ( 'qv_xy', 'qv_xz', 'qv_yz' )
736                IF ( av == 0 )  THEN
737                   DO  i = nxl, nxr
738                      DO  j = nys, nyn
739                         DO  k = nzb, nzt+1
740                            local_pf(i,j,k) = q(k,j,i) - ql(k,j,i)
741                         ENDDO
742                      ENDDO
743                   ENDDO
744                   resorted = .TRUE.
745                ELSE
746                   IF ( .NOT. ALLOCATED( qv_av ) ) THEN
747                      ALLOCATE( qv_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
748                      qv_av = REAL( fill_value, KIND = wp )
749                   ENDIF
750                   to_be_resorted => qv_av
751                ENDIF
752                IF ( mode == 'xy' )  level_z = zu
753
754             CASE ( 'r_a*_xy' )        ! 2d-array
755                IF ( av == 0 )  THEN
756                   DO  m = 1, surf_lsm_h%ns
757                      i                   = surf_lsm_h%i(m)           
758                      j                   = surf_lsm_h%j(m)
759                      local_pf(i,j,nzb+1) = surf_lsm_h%r_a(m)
760                   ENDDO
761
762                   DO  m = 1, surf_usm_h%ns
763                      i   = surf_usm_h%i(m)           
764                      j   = surf_usm_h%j(m)
765                      local_pf(i,j,nzb+1) =                                          &
766                                 ( surf_usm_h%frac(m,ind_veg_wall)  *                &
767                                   surf_usm_h%r_a(m)       +                         & 
768                                   surf_usm_h%frac(m,ind_pav_green) *                &
769                                   surf_usm_h%r_a_green(m) +                         & 
770                                   surf_usm_h%frac(m,ind_wat_win)   *                &
771                                   surf_usm_h%r_a_window(m) )
772                   ENDDO
773                ELSE
774                   IF ( .NOT. ALLOCATED( r_a_av ) ) THEN
775                      ALLOCATE( r_a_av(nysg:nyng,nxlg:nxrg) )
776                      r_a_av = REAL( fill_value, KIND = wp )
777                   ENDIF
778                   DO  i = nxl, nxr
779                      DO  j = nys, nyn
780                         local_pf(i,j,nzb+1) = r_a_av(j,i)
781                      ENDDO
782                   ENDDO
783                ENDIF
784                resorted       = .TRUE.
785                two_d          = .TRUE.
786                level_z(nzb+1) = zu(nzb+1)
787
788             CASE ( 's_xy', 's_xz', 's_yz' )
789                IF ( av == 0 )  THEN
790                   to_be_resorted => s
791                ELSE
792                   IF ( .NOT. ALLOCATED( s_av ) ) THEN
793                      ALLOCATE( s_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
794                      s_av = REAL( fill_value, KIND = wp )
795                   ENDIF
796                   to_be_resorted => s_av
797                ENDIF
798
799             CASE ( 'shf*_xy' )        ! 2d-array
800                IF ( av == 0 ) THEN
801!
802!--                In case of default surfaces, clean-up flux by density.
803!--                In case of land- and urban-surfaces, convert fluxes into
804!--                dynamic units.
805                   DO  m = 1, surf_def_h(0)%ns
806                      i = surf_def_h(0)%i(m)
807                      j = surf_def_h(0)%j(m)
808                      k = surf_def_h(0)%k(m)
809                      local_pf(i,j,nzb+1) = surf_def_h(0)%shf(m) *             &
810                                            heatflux_output_conversion(k)
811                   ENDDO
812                   DO  m = 1, surf_lsm_h%ns
813                      i = surf_lsm_h%i(m)
814                      j = surf_lsm_h%j(m)
815                      k = surf_lsm_h%k(m)
816                      local_pf(i,j,nzb+1) = surf_lsm_h%shf(m) * c_p
817                   ENDDO
818                   DO  m = 1, surf_usm_h%ns
819                      i = surf_usm_h%i(m)
820                      j = surf_usm_h%j(m)
821                      k = surf_usm_h%k(m)
822                      local_pf(i,j,nzb+1) = surf_usm_h%shf(m) * c_p
823                   ENDDO
824                ELSE
825                   IF ( .NOT. ALLOCATED( shf_av ) ) THEN
826                      ALLOCATE( shf_av(nysg:nyng,nxlg:nxrg) )
827                      shf_av = REAL( fill_value, KIND = wp )
828                   ENDIF
829                   DO  i = nxl, nxr
830                      DO  j = nys, nyn
831                         local_pf(i,j,nzb+1) =  shf_av(j,i)
832                      ENDDO
833                   ENDDO
834                ENDIF
835                resorted = .TRUE.
836                two_d = .TRUE.
837                level_z(nzb+1) = zu(nzb+1)
838               
839             CASE ( 'ssws*_xy' )        ! 2d-array
840                IF ( av == 0 ) THEN
841                   DO  m = 1, surf_def_h(0)%ns
842                      i = surf_def_h(0)%i(m)
843                      j = surf_def_h(0)%j(m)
844                      local_pf(i,j,nzb+1) = surf_def_h(0)%ssws(m)
845                   ENDDO
846                   DO  m = 1, surf_lsm_h%ns
847                      i = surf_lsm_h%i(m)
848                      j = surf_lsm_h%j(m)
849                      local_pf(i,j,nzb+1) = surf_lsm_h%ssws(m)
850                   ENDDO
851                   DO  m = 1, surf_usm_h%ns
852                      i = surf_usm_h%i(m)
853                      j = surf_usm_h%j(m)
854                      local_pf(i,j,nzb+1) = surf_usm_h%ssws(m)
855                   ENDDO
856                ELSE
857                   IF ( .NOT. ALLOCATED( ssws_av ) ) THEN
858                      ALLOCATE( ssws_av(nysg:nyng,nxlg:nxrg) )
859                      ssws_av = REAL( fill_value, KIND = wp )
860                   ENDIF
861                   DO  i = nxl, nxr
862                      DO  j = nys, nyn 
863                         local_pf(i,j,nzb+1) =  ssws_av(j,i)
864                      ENDDO
865                   ENDDO
866                ENDIF
867                resorted = .TRUE.
868                two_d = .TRUE.
869                level_z(nzb+1) = zu(nzb+1)               
870
871             CASE ( 't*_xy' )        ! 2d-array
872                IF ( av == 0 )  THEN
873                   DO  m = 1, surf_def_h(0)%ns
874                      i = surf_def_h(0)%i(m)
875                      j = surf_def_h(0)%j(m)
876                      local_pf(i,j,nzb+1) = surf_def_h(0)%ts(m)
877                   ENDDO
878                   DO  m = 1, surf_lsm_h%ns
879                      i = surf_lsm_h%i(m)
880                      j = surf_lsm_h%j(m)
881                      local_pf(i,j,nzb+1) = surf_lsm_h%ts(m)
882                   ENDDO
883                   DO  m = 1, surf_usm_h%ns
884                      i = surf_usm_h%i(m)
885                      j = surf_usm_h%j(m)
886                      local_pf(i,j,nzb+1) = surf_usm_h%ts(m)
887                   ENDDO
888                ELSE
889                   IF ( .NOT. ALLOCATED( ts_av ) ) THEN
890                      ALLOCATE( ts_av(nysg:nyng,nxlg:nxrg) )
891                      ts_av = REAL( fill_value, KIND = wp )
892                   ENDIF
893                   DO  i = nxl, nxr
894                      DO  j = nys, nyn
895                         local_pf(i,j,nzb+1) = ts_av(j,i)
896                      ENDDO
897                   ENDDO
898                ENDIF
899                resorted = .TRUE.
900                two_d = .TRUE.
901                level_z(nzb+1) = zu(nzb+1)
902
903             CASE ( 'tsurf*_xy' )        ! 2d-array
904                IF ( av == 0 )  THEN
905                   DO  m = 1, surf_def_h(0)%ns
906                      i                   = surf_def_h(0)%i(m)           
907                      j                   = surf_def_h(0)%j(m)
908                      local_pf(i,j,nzb+1) = surf_def_h(0)%pt_surface(m)
909                   ENDDO
910
911                   DO  m = 1, surf_lsm_h%ns
912                      i                   = surf_lsm_h%i(m)           
913                      j                   = surf_lsm_h%j(m)
914                      local_pf(i,j,nzb+1) = surf_lsm_h%pt_surface(m)
915                   ENDDO
916
917                   DO  m = 1, surf_usm_h%ns
918                      i   = surf_usm_h%i(m)           
919                      j   = surf_usm_h%j(m)
920                      local_pf(i,j,nzb+1) = surf_usm_h%pt_surface(m)
921                   ENDDO
922
923                ELSE
924                   IF ( .NOT. ALLOCATED( tsurf_av ) ) THEN
925                      ALLOCATE( tsurf_av(nysg:nyng,nxlg:nxrg) )
926                      tsurf_av = REAL( fill_value, KIND = wp )
927                   ENDIF
928                   DO  i = nxl, nxr
929                      DO  j = nys, nyn
930                         local_pf(i,j,nzb+1) = tsurf_av(j,i)
931                      ENDDO
932                   ENDDO
933                ENDIF
934                resorted       = .TRUE.
935                two_d          = .TRUE.
936                level_z(nzb+1) = zu(nzb+1)
937
938             CASE ( 'u_xy', 'u_xz', 'u_yz' )
939                flag_nr = 1
940                IF ( av == 0 )  THEN
941                   to_be_resorted => u
942                ELSE
943                   IF ( .NOT. ALLOCATED( u_av ) ) THEN
944                      ALLOCATE( u_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
945                      u_av = REAL( fill_value, KIND = wp )
946                   ENDIF
947                   to_be_resorted => u_av
948                ENDIF
949                IF ( mode == 'xy' )  level_z = zu
950!
951!--             Substitute the values generated by "mirror" boundary condition
952!--             at the bottom boundary by the real surface values.
953                IF ( do2d(av,ivar) == 'u_xz'  .OR.  do2d(av,ivar) == 'u_yz' )  THEN
954                   IF ( ibc_uv_b == 0 )  local_pf(:,:,nzb) = 0.0_wp
955                ENDIF
956               
957             CASE ( 'us*_xy' )        ! 2d-array
958                IF ( av == 0 )  THEN
959                   DO  m = 1, surf_def_h(0)%ns
960                      i = surf_def_h(0)%i(m)
961                      j = surf_def_h(0)%j(m)
962                      local_pf(i,j,nzb+1) = surf_def_h(0)%us(m)
963                   ENDDO
964                   DO  m = 1, surf_lsm_h%ns
965                      i = surf_lsm_h%i(m)
966                      j = surf_lsm_h%j(m)
967                      local_pf(i,j,nzb+1) = surf_lsm_h%us(m)
968                   ENDDO
969                   DO  m = 1, surf_usm_h%ns
970                      i = surf_usm_h%i(m)
971                      j = surf_usm_h%j(m)
972                      local_pf(i,j,nzb+1) = surf_usm_h%us(m)
973                   ENDDO
974                ELSE
975                   IF ( .NOT. ALLOCATED( us_av ) ) THEN
976                      ALLOCATE( us_av(nysg:nyng,nxlg:nxrg) )
977                      us_av = REAL( fill_value, KIND = wp )
978                   ENDIF
979                   DO  i = nxl, nxr
980                      DO  j = nys, nyn
981                         local_pf(i,j,nzb+1) = us_av(j,i)
982                      ENDDO
983                   ENDDO
984                ENDIF
985                resorted = .TRUE.
986                two_d = .TRUE.
987                level_z(nzb+1) = zu(nzb+1)
988
989             CASE ( 'v_xy', 'v_xz', 'v_yz' )
990                flag_nr = 2
991                IF ( av == 0 )  THEN
992                   to_be_resorted => v
993                ELSE
994                   IF ( .NOT. ALLOCATED( v_av ) ) THEN
995                      ALLOCATE( v_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
996                      v_av = REAL( fill_value, KIND = wp )
997                   ENDIF
998                   to_be_resorted => v_av
999                ENDIF
1000                IF ( mode == 'xy' )  level_z = zu
1001!
1002!--             Substitute the values generated by "mirror" boundary condition
1003!--             at the bottom boundary by the real surface values.
1004                IF ( do2d(av,ivar) == 'v_xz'  .OR.  do2d(av,ivar) == 'v_yz' )  THEN
1005                   IF ( ibc_uv_b == 0 )  local_pf(:,:,nzb) = 0.0_wp
1006                ENDIF
1007
1008             CASE ( 'thetav_xy', 'thetav_xz', 'thetav_yz' )
1009                IF ( av == 0 )  THEN
1010                   to_be_resorted => vpt
1011                ELSE
1012                   IF ( .NOT. ALLOCATED( vpt_av ) ) THEN
1013                      ALLOCATE( vpt_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1014                      vpt_av = REAL( fill_value, KIND = wp )
1015                   ENDIF
1016                   to_be_resorted => vpt_av
1017                ENDIF
1018                IF ( mode == 'xy' )  level_z = zu
1019
1020             CASE ( 'w_xy', 'w_xz', 'w_yz' )
1021                flag_nr = 3
1022                IF ( av == 0 )  THEN
1023                   to_be_resorted => w
1024                ELSE
1025                   IF ( .NOT. ALLOCATED( w_av ) ) THEN
1026                      ALLOCATE( w_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1027                      w_av = REAL( fill_value, KIND = wp )
1028                   ENDIF
1029                   to_be_resorted => w_av
1030                ENDIF
1031                IF ( mode == 'xy' )  level_z = zw
1032
1033             CASE ( 'z0*_xy' )        ! 2d-array
1034                IF ( av == 0 ) THEN
1035                   DO  m = 1, surf_def_h(0)%ns
1036                      i = surf_def_h(0)%i(m)
1037                      j = surf_def_h(0)%j(m)
1038                      local_pf(i,j,nzb+1) = surf_def_h(0)%z0(m)
1039                   ENDDO
1040                   DO  m = 1, surf_lsm_h%ns
1041                      i = surf_lsm_h%i(m)
1042                      j = surf_lsm_h%j(m)
1043                      local_pf(i,j,nzb+1) = surf_lsm_h%z0(m)
1044                   ENDDO
1045                   DO  m = 1, surf_usm_h%ns
1046                      i = surf_usm_h%i(m)
1047                      j = surf_usm_h%j(m)
1048                      local_pf(i,j,nzb+1) = surf_usm_h%z0(m)
1049                   ENDDO
1050                ELSE
1051                   IF ( .NOT. ALLOCATED( z0_av ) ) THEN
1052                      ALLOCATE( z0_av(nysg:nyng,nxlg:nxrg) )
1053                      z0_av = REAL( fill_value, KIND = wp )
1054                   ENDIF
1055                   DO  i = nxl, nxr
1056                      DO  j = nys, nyn
1057                         local_pf(i,j,nzb+1) =  z0_av(j,i)
1058                      ENDDO
1059                   ENDDO
1060                ENDIF
1061                resorted = .TRUE.
1062                two_d = .TRUE.
1063                level_z(nzb+1) = zu(nzb+1)
1064
1065             CASE ( 'z0h*_xy' )        ! 2d-array
1066                IF ( av == 0 ) THEN
1067                   DO  m = 1, surf_def_h(0)%ns
1068                      i = surf_def_h(0)%i(m)
1069                      j = surf_def_h(0)%j(m)
1070                      local_pf(i,j,nzb+1) = surf_def_h(0)%z0h(m)
1071                   ENDDO
1072                   DO  m = 1, surf_lsm_h%ns
1073                      i = surf_lsm_h%i(m)
1074                      j = surf_lsm_h%j(m)
1075                      local_pf(i,j,nzb+1) = surf_lsm_h%z0h(m)
1076                   ENDDO
1077                   DO  m = 1, surf_usm_h%ns
1078                      i = surf_usm_h%i(m)
1079                      j = surf_usm_h%j(m)
1080                      local_pf(i,j,nzb+1) = surf_usm_h%z0h(m)
1081                   ENDDO
1082                ELSE
1083                   IF ( .NOT. ALLOCATED( z0h_av ) ) THEN
1084                      ALLOCATE( z0h_av(nysg:nyng,nxlg:nxrg) )
1085                      z0h_av = REAL( fill_value, KIND = wp )
1086                   ENDIF
1087                   DO  i = nxl, nxr
1088                      DO  j = nys, nyn
1089                         local_pf(i,j,nzb+1) =  z0h_av(j,i)
1090                      ENDDO
1091                   ENDDO
1092                ENDIF
1093                resorted = .TRUE.
1094                two_d = .TRUE.
1095                level_z(nzb+1) = zu(nzb+1)
1096
1097             CASE ( 'z0q*_xy' )        ! 2d-array
1098                IF ( av == 0 ) THEN
1099                   DO  m = 1, surf_def_h(0)%ns
1100                      i = surf_def_h(0)%i(m)
1101                      j = surf_def_h(0)%j(m)
1102                      local_pf(i,j,nzb+1) = surf_def_h(0)%z0q(m)
1103                   ENDDO
1104                   DO  m = 1, surf_lsm_h%ns
1105                      i = surf_lsm_h%i(m)
1106                      j = surf_lsm_h%j(m)
1107                      local_pf(i,j,nzb+1) = surf_lsm_h%z0q(m)
1108                   ENDDO
1109                   DO  m = 1, surf_usm_h%ns
1110                      i = surf_usm_h%i(m)
1111                      j = surf_usm_h%j(m)
1112                      local_pf(i,j,nzb+1) = surf_usm_h%z0q(m)
1113                   ENDDO
1114                ELSE
1115                   IF ( .NOT. ALLOCATED( z0q_av ) ) THEN
1116                      ALLOCATE( z0q_av(nysg:nyng,nxlg:nxrg) )
1117                      z0q_av = REAL( fill_value, KIND = wp )
1118                   ENDIF
1119                   DO  i = nxl, nxr
1120                      DO  j = nys, nyn
1121                         local_pf(i,j,nzb+1) =  z0q_av(j,i)
1122                      ENDDO
1123                   ENDDO
1124                ENDIF
1125                resorted = .TRUE.
1126                two_d = .TRUE.
1127                level_z(nzb+1) = zu(nzb+1)
1128
1129             CASE DEFAULT
1130
1131!
1132!--             Quantities of other modules
1133                IF ( .NOT. found )  THEN
1134                   CALL module_interface_data_output_2d(                       &
1135                           av, do2d(av,ivar), found, grid, mode,               &
1136                           local_pf, two_d, nzb_do, nzt_do,                    &
1137                           fill_value                                          &
1138                        )
1139                ENDIF
1140
1141                resorted = .TRUE.
1142
1143                IF ( grid == 'zu' )  THEN
1144                   IF ( mode == 'xy' )  level_z = zu
1145                ELSEIF ( grid == 'zw' )  THEN
1146                   IF ( mode == 'xy' )  level_z = zw
1147                ELSEIF ( grid == 'zu1' ) THEN
1148                   IF ( mode == 'xy' )  level_z(nzb+1) = zu(nzb+1)
1149                ELSEIF ( grid == 'zs' ) THEN
1150                   IF ( mode == 'xy' )  level_z = zs
1151                ENDIF
1152
1153                IF ( .NOT. found )  THEN
1154                   message_string = 'no output provided for: ' //              &
1155                                    TRIM( do2d(av,ivar) )
1156                   CALL message( 'data_output_2d', 'PA0181', 0, 0, 0, 6, 0 )
1157                ENDIF
1158
1159          END SELECT
1160
1161!
1162!--       Resort the array to be output, if not done above. Flag topography
1163!--       grid points with fill values, using the corresponding maksing flag.
1164          IF ( .NOT. resorted )  THEN
1165             DO  i = nxl, nxr
1166                DO  j = nys, nyn
1167                   DO  k = nzb_do, nzt_do
1168                      local_pf(i,j,k) = MERGE( to_be_resorted(k,j,i),          &
1169                                           REAL( fill_value, KIND = wp ),      &
1170                                           BTEST( wall_flags_total_0(k,j,i),   &
1171                                                  flag_nr ) ) 
1172                   ENDDO
1173                ENDDO
1174             ENDDO
1175          ENDIF
1176
1177!
1178!--       Output of the individual cross-sections, depending on the cross-
1179!--       section mode chosen.
1180          is = 1
1181   loop1: DO WHILE ( section(is,s_ind) /= -9999  .OR.  two_d )
1182
1183             SELECT CASE ( mode )
1184
1185                CASE ( 'xy' )
1186!
1187!--                Determine the cross section index
1188                   IF ( two_d )  THEN
1189                      layer_xy = nzb+1
1190                   ELSE
1191                      layer_xy = section(is,s_ind)
1192                   ENDIF
1193
1194!
1195!--                Exit the loop for layers beyond the data output domain
1196!--                (used for soil model)
1197                   IF ( layer_xy > nzt_do )  THEN
1198                      EXIT loop1
1199                   ENDIF
1200
1201!
1202!--                Update the netCDF xy cross section time axis.
1203!--                In case of parallel output, this is only done by PE0
1204!--                to increase the performance.
1205                   IF ( time_since_reference_point /= do2d_xy_last_time(av) )  THEN
1206                      do2d_xy_time_count(av) = do2d_xy_time_count(av) + 1
1207                      do2d_xy_last_time(av)  = time_since_reference_point
1208                      IF ( myid == 0 )  THEN
1209                         IF ( .NOT. data_output_2d_on_each_pe  &
1210                              .OR.  netcdf_data_format > 4 )   &
1211                         THEN
1212#if defined( __netcdf )
1213                            nc_stat = NF90_PUT_VAR( id_set_xy(av),             &
1214                                                    id_var_time_xy(av),        &
1215                                             (/ time_since_reference_point /), &
1216                                         start = (/ do2d_xy_time_count(av) /), &
1217                                                    count = (/ 1 /) )
1218                            CALL netcdf_handle_error( 'data_output_2d', 53 )
1219#endif
1220                         ENDIF
1221                      ENDIF
1222                   ENDIF
1223!
1224!--                If required, carry out averaging along z
1225                   IF ( section(is,s_ind) == -1  .AND.  .NOT. two_d )  THEN
1226
1227                      local_2d = 0.0_wp
1228!
1229!--                   Carry out the averaging (all data are on the PE)
1230                      DO  k = nzb_do, nzt_do
1231                         DO  j = nys, nyn
1232                            DO  i = nxl, nxr
1233                               local_2d(i,j) = local_2d(i,j) + local_pf(i,j,k)
1234                            ENDDO
1235                         ENDDO
1236                      ENDDO
1237
1238                      local_2d = local_2d / ( nzt_do - nzb_do + 1.0_wp)
1239
1240                   ELSE
1241!
1242!--                   Just store the respective section on the local array
1243                      local_2d = local_pf(:,:,layer_xy)
1244
1245                   ENDIF
1246
1247#if defined( __parallel )
1248                   IF ( netcdf_data_format > 4 )  THEN
1249!
1250!--                   Parallel output in netCDF4/HDF5 format.
1251                      IF ( two_d ) THEN
1252                         iis = 1
1253                      ELSE
1254                         iis = is
1255                      ENDIF
1256
1257#if defined( __netcdf )
1258!
1259!--                   For parallel output, all cross sections are first stored
1260!--                   here on a local array and will be written to the output
1261!--                   file afterwards to increase the performance.
1262                      DO  i = nxl, nxr
1263                         DO  j = nys, nyn
1264                            local_2d_sections(i,j,iis) = local_2d(i,j)
1265                         ENDDO
1266                      ENDDO
1267#endif
1268                   ELSE
1269
1270                      IF ( data_output_2d_on_each_pe )  THEN
1271!
1272!--                      Output of partial arrays on each PE
1273#if defined( __netcdf )
1274                         IF ( myid == 0 )  THEN
1275                            WRITE ( 21 )  time_since_reference_point,          &
1276                                          do2d_xy_time_count(av), av
1277                         ENDIF
1278#endif
1279                         DO  i = 0, io_blocks-1
1280                            IF ( i == io_group )  THEN
1281                               WRITE ( 21 )  nxl, nxr, nys, nyn, nys, nyn
1282                               WRITE ( 21 )  local_2d
1283                            ENDIF
1284#if defined( __parallel )
1285                            CALL MPI_BARRIER( comm2d, ierr )
1286#endif
1287                         ENDDO
1288
1289                      ELSE
1290!
1291!--                      PE0 receives partial arrays from all processors and
1292!--                      then outputs them. Here a barrier has to be set,
1293!--                      because otherwise "-MPI- FATAL: Remote protocol queue
1294!--                      full" may occur.
1295                         CALL MPI_BARRIER( comm2d, ierr )
1296
1297                         ngp = ( nxr-nxl+1 ) * ( nyn-nys+1 )
1298                         IF ( myid == 0 )  THEN
1299!
1300!--                         Local array can be relocated directly.
1301                            total_2d(nxl:nxr,nys:nyn) = local_2d
1302!
1303!--                         Receive data from all other PEs.
1304                            DO  n = 1, numprocs-1
1305!
1306!--                            Receive index limits first, then array.
1307!--                            Index limits are received in arbitrary order from
1308!--                            the PEs.
1309                               CALL MPI_RECV( ind(1), 4, MPI_INTEGER,          &
1310                                              MPI_ANY_SOURCE, 0, comm2d,       &
1311                                              status, ierr )
1312                               sender = status(MPI_SOURCE)
1313                               DEALLOCATE( local_2d )
1314                               ALLOCATE( local_2d(ind(1):ind(2),ind(3):ind(4)) )
1315                               CALL MPI_RECV( local_2d(ind(1),ind(3)), ngp,    &
1316                                              MPI_REAL, sender, 1, comm2d,     &
1317                                              status, ierr )
1318                               total_2d(ind(1):ind(2),ind(3):ind(4)) = local_2d
1319                            ENDDO
1320!
1321!--                         Relocate the local array for the next loop increment
1322                            DEALLOCATE( local_2d )
1323                            ALLOCATE( local_2d(nxl:nxr,nys:nyn) )
1324
1325#if defined( __netcdf )
1326                            IF ( two_d ) THEN
1327                               nc_stat = NF90_PUT_VAR( id_set_xy(av),       &
1328                                                       id_var_do2d(av,ivar),  &
1329                                                       total_2d(0:nx,0:ny), &
1330                             start = (/ 1, 1, 1, do2d_xy_time_count(av) /), &
1331                                             count = (/ nx+1, ny+1, 1, 1 /) )
1332                            ELSE
1333                               nc_stat = NF90_PUT_VAR( id_set_xy(av),       &
1334                                                       id_var_do2d(av,ivar),  &
1335                                                       total_2d(0:nx,0:ny), &
1336                            start = (/ 1, 1, is, do2d_xy_time_count(av) /), &
1337                                             count = (/ nx+1, ny+1, 1, 1 /) )
1338                            ENDIF
1339                            CALL netcdf_handle_error( 'data_output_2d', 54 )
1340#endif
1341
1342                         ELSE
1343!
1344!--                         First send the local index limits to PE0
1345                            ind(1) = nxl; ind(2) = nxr
1346                            ind(3) = nys; ind(4) = nyn
1347                            CALL MPI_SEND( ind(1), 4, MPI_INTEGER, 0, 0,       &
1348                                           comm2d, ierr )
1349!
1350!--                         Send data to PE0
1351                            CALL MPI_SEND( local_2d(nxl,nys), ngp,             &
1352                                           MPI_REAL, 0, 1, comm2d, ierr )
1353                         ENDIF
1354!
1355!--                      A barrier has to be set, because otherwise some PEs may
1356!--                      proceed too fast so that PE0 may receive wrong data on
1357!--                      tag 0
1358                         CALL MPI_BARRIER( comm2d, ierr )
1359                      ENDIF
1360
1361                   ENDIF
1362#else
1363#if defined( __netcdf )
1364                   IF ( two_d ) THEN
1365                      nc_stat = NF90_PUT_VAR( id_set_xy(av),                &
1366                                              id_var_do2d(av,ivar),           &
1367                                              local_2d(nxl:nxr,nys:nyn),    &
1368                             start = (/ 1, 1, 1, do2d_xy_time_count(av) /), &
1369                                           count = (/ nx+1, ny+1, 1, 1 /) )
1370                   ELSE
1371                      nc_stat = NF90_PUT_VAR( id_set_xy(av),                &
1372                                              id_var_do2d(av,ivar),           &
1373                                              local_2d(nxl:nxr,nys:nyn),    &
1374                            start = (/ 1, 1, is, do2d_xy_time_count(av) /), &
1375                                           count = (/ nx+1, ny+1, 1, 1 /) )
1376                   ENDIF
1377                   CALL netcdf_handle_error( 'data_output_2d', 447 )
1378#endif
1379#endif
1380
1381!
1382!--                For 2D-arrays (e.g. u*) only one cross-section is available.
1383!--                Hence exit loop of output levels.
1384                   IF ( two_d )  THEN
1385                      IF ( netcdf_data_format < 5 )  two_d = .FALSE.
1386                      EXIT loop1
1387                   ENDIF
1388
1389                CASE ( 'xz' )
1390!
1391!--                Update the netCDF xz cross section time axis.
1392!--                In case of parallel output, this is only done by PE0
1393!--                to increase the performance.
1394                   IF ( time_since_reference_point /= do2d_xz_last_time(av) )  THEN
1395                      do2d_xz_time_count(av) = do2d_xz_time_count(av) + 1
1396                      do2d_xz_last_time(av)  = time_since_reference_point
1397                      IF ( myid == 0 )  THEN
1398                         IF ( .NOT. data_output_2d_on_each_pe  &
1399                              .OR.  netcdf_data_format > 4 )   &
1400                         THEN
1401#if defined( __netcdf )
1402                            nc_stat = NF90_PUT_VAR( id_set_xz(av),             &
1403                                                    id_var_time_xz(av),        &
1404                                             (/ time_since_reference_point /), &
1405                                         start = (/ do2d_xz_time_count(av) /), &
1406                                                    count = (/ 1 /) )
1407                            CALL netcdf_handle_error( 'data_output_2d', 56 )
1408#endif
1409                         ENDIF
1410                      ENDIF
1411                   ENDIF
1412
1413!
1414!--                If required, carry out averaging along y
1415                   IF ( section(is,s_ind) == -1 )  THEN
1416
1417                      ALLOCATE( local_2d_l(nxl:nxr,nzb_do:nzt_do) )
1418                      local_2d_l = 0.0_wp
1419                      ngp = ( nxr-nxl + 1 ) * ( nzt_do-nzb_do + 1 )
1420!
1421!--                   First local averaging on the PE
1422                      DO  k = nzb_do, nzt_do
1423                         DO  j = nys, nyn
1424                            DO  i = nxl, nxr
1425                               local_2d_l(i,k) = local_2d_l(i,k) +             &
1426                                                 local_pf(i,j,k)
1427                            ENDDO
1428                         ENDDO
1429                      ENDDO
1430#if defined( __parallel )
1431!
1432!--                   Now do the averaging over all PEs along y
1433                      IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
1434                      CALL MPI_ALLREDUCE( local_2d_l(nxl,nzb_do),                &
1435                                          local_2d(nxl,nzb_do), ngp, MPI_REAL,   &
1436                                          MPI_SUM, comm1dy, ierr )
1437#else
1438                      local_2d = local_2d_l
1439#endif
1440                      local_2d = local_2d / ( ny + 1.0_wp )
1441
1442                      DEALLOCATE( local_2d_l )
1443
1444                   ELSE
1445!
1446!--                   Just store the respective section on the local array
1447!--                   (but only if it is available on this PE!)
1448                      IF ( section(is,s_ind) >= nys  .AND.  section(is,s_ind) <= nyn ) &
1449                      THEN
1450                         local_2d = local_pf(:,section(is,s_ind),nzb_do:nzt_do)
1451                      ENDIF
1452
1453                   ENDIF
1454
1455#if defined( __parallel )
1456                   IF ( netcdf_data_format > 4 )  THEN
1457!
1458!--                   Output in netCDF4/HDF5 format.
1459!--                   Output only on those PEs where the respective cross
1460!--                   sections reside. Cross sections averaged along y are
1461!--                   output on the respective first PE along y (myidy=0).
1462                      IF ( ( section(is,s_ind) >= nys  .AND.                   &
1463                             section(is,s_ind) <= nyn )  .OR.                  &
1464                           ( section(is,s_ind) == -1  .AND.  myidy == 0 ) )  THEN
1465#if defined( __netcdf )
1466!
1467!--                      For parallel output, all cross sections are first
1468!--                      stored here on a local array and will be written to the
1469!--                      output file afterwards to increase the performance.
1470                         DO  i = nxl, nxr
1471                            DO  k = nzb_do, nzt_do
1472                               local_2d_sections_l(i,is,k) = local_2d(i,k)
1473                            ENDDO
1474                         ENDDO
1475#endif
1476                      ENDIF
1477
1478                   ELSE
1479
1480                      IF ( data_output_2d_on_each_pe )  THEN
1481!
1482!--                      Output of partial arrays on each PE. If the cross
1483!--                      section does not reside on the PE, output special
1484!--                      index values.
1485#if defined( __netcdf )
1486                         IF ( myid == 0 )  THEN
1487                            WRITE ( 22 )  time_since_reference_point,          &
1488                                          do2d_xz_time_count(av), av
1489                         ENDIF
1490#endif
1491                         DO  i = 0, io_blocks-1
1492                            IF ( i == io_group )  THEN
1493                               IF ( ( section(is,s_ind) >= nys  .AND.          &
1494                                      section(is,s_ind) <= nyn )  .OR.         &
1495                                    ( section(is,s_ind) == -1  .AND.           &
1496                                      nys-1 == -1 ) )                          &
1497                               THEN
1498                                  WRITE (22)  nxl, nxr, nzb_do, nzt_do, nzb, nzt+1
1499                                  WRITE (22)  local_2d
1500                               ELSE
1501                                  WRITE (22)  -1, -1, -1, -1, -1, -1
1502                               ENDIF
1503                            ENDIF
1504#if defined( __parallel )
1505                            CALL MPI_BARRIER( comm2d, ierr )
1506#endif
1507                         ENDDO
1508
1509                      ELSE
1510!
1511!--                      PE0 receives partial arrays from all processors of the
1512!--                      respective cross section and outputs them. Here a
1513!--                      barrier has to be set, because otherwise
1514!--                      "-MPI- FATAL: Remote protocol queue full" may occur.
1515                         CALL MPI_BARRIER( comm2d, ierr )
1516
1517                         ngp = ( nxr-nxl + 1 ) * ( nzt_do-nzb_do + 1 )
1518                         IF ( myid == 0 )  THEN
1519!
1520!--                         Local array can be relocated directly.
1521                            IF ( ( section(is,s_ind) >= nys  .AND.              &
1522                                   section(is,s_ind) <= nyn )  .OR.             &
1523                                 ( section(is,s_ind) == -1  .AND.               &
1524                                   nys-1 == -1 ) )  THEN
1525                               total_2d(nxl:nxr,nzb_do:nzt_do) = local_2d
1526                            ENDIF
1527!
1528!--                         Receive data from all other PEs.
1529                            DO  n = 1, numprocs-1
1530!
1531!--                            Receive index limits first, then array.
1532!--                            Index limits are received in arbitrary order from
1533!--                            the PEs.
1534                               CALL MPI_RECV( ind(1), 4, MPI_INTEGER,          &
1535                                              MPI_ANY_SOURCE, 0, comm2d,       &
1536                                              status, ierr )
1537!
1538!--                            Not all PEs have data for XZ-cross-section.
1539                               IF ( ind(1) /= -9999 )  THEN
1540                                  sender = status(MPI_SOURCE)
1541                                  DEALLOCATE( local_2d )
1542                                  ALLOCATE( local_2d(ind(1):ind(2),            &
1543                                                     ind(3):ind(4)) )
1544                                  CALL MPI_RECV( local_2d(ind(1),ind(3)), ngp, &
1545                                                 MPI_REAL, sender, 1, comm2d,  &
1546                                                 status, ierr )
1547                                  total_2d(ind(1):ind(2),ind(3):ind(4)) =      &
1548                                                                        local_2d
1549                               ENDIF
1550                            ENDDO
1551!
1552!--                         Relocate the local array for the next loop increment
1553                            DEALLOCATE( local_2d )
1554                            ALLOCATE( local_2d(nxl:nxr,nzb_do:nzt_do) )
1555
1556#if defined( __netcdf )
1557                            nc_stat = NF90_PUT_VAR( id_set_xz(av),             &
1558                                                 id_var_do2d(av,ivar),           &
1559                                                 total_2d(0:nx,nzb_do:nzt_do), &
1560                               start = (/ 1, is, 1, do2d_xz_time_count(av) /), &
1561                                          count = (/ nx+1, 1, nzt_do-nzb_do+1, 1 /) )
1562                            CALL netcdf_handle_error( 'data_output_2d', 58 )
1563#endif
1564
1565                         ELSE
1566!
1567!--                         If the cross section resides on the PE, send the
1568!--                         local index limits, otherwise send -9999 to PE0.
1569                            IF ( ( section(is,s_ind) >= nys  .AND.              &
1570                                   section(is,s_ind) <= nyn )  .OR.             &
1571                                 ( section(is,s_ind) == -1  .AND.  nys-1 == -1 ) ) &
1572                            THEN
1573                               ind(1) = nxl; ind(2) = nxr
1574                               ind(3) = nzb_do;   ind(4) = nzt_do
1575                            ELSE
1576                               ind(1) = -9999; ind(2) = -9999
1577                               ind(3) = -9999; ind(4) = -9999
1578                            ENDIF
1579                            CALL MPI_SEND( ind(1), 4, MPI_INTEGER, 0, 0,       &
1580                                           comm2d, ierr )
1581!
1582!--                         If applicable, send data to PE0.
1583                            IF ( ind(1) /= -9999 )  THEN
1584                               CALL MPI_SEND( local_2d(nxl,nzb_do), ngp,         &
1585                                              MPI_REAL, 0, 1, comm2d, ierr )
1586                            ENDIF
1587                         ENDIF
1588!
1589!--                      A barrier has to be set, because otherwise some PEs may
1590!--                      proceed too fast so that PE0 may receive wrong data on
1591!--                      tag 0
1592                         CALL MPI_BARRIER( comm2d, ierr )
1593                      ENDIF
1594
1595                   ENDIF
1596#else
1597#if defined( __netcdf )
1598                   nc_stat = NF90_PUT_VAR( id_set_xz(av),                   &
1599                                           id_var_do2d(av,ivar),              &
1600                                           local_2d(nxl:nxr,nzb_do:nzt_do), &
1601                            start = (/ 1, is, 1, do2d_xz_time_count(av) /), &
1602                                       count = (/ nx+1, 1, nzt_do-nzb_do+1, 1 /) )
1603                   CALL netcdf_handle_error( 'data_output_2d', 451 )
1604#endif
1605#endif
1606
1607                CASE ( 'yz' )
1608!
1609!--                Update the netCDF yz cross section time axis.
1610!--                In case of parallel output, this is only done by PE0
1611!--                to increase the performance.
1612                   IF ( time_since_reference_point /= do2d_yz_last_time(av) )  THEN
1613                      do2d_yz_time_count(av) = do2d_yz_time_count(av) + 1
1614                      do2d_yz_last_time(av)  = time_since_reference_point
1615                      IF ( myid == 0 )  THEN
1616                         IF ( .NOT. data_output_2d_on_each_pe  &
1617                              .OR.  netcdf_data_format > 4 )   &
1618                         THEN
1619#if defined( __netcdf )
1620                            nc_stat = NF90_PUT_VAR( id_set_yz(av),             &
1621                                                    id_var_time_yz(av),        &
1622                                             (/ time_since_reference_point /), &
1623                                         start = (/ do2d_yz_time_count(av) /), &
1624                                                    count = (/ 1 /) )
1625                            CALL netcdf_handle_error( 'data_output_2d', 59 )
1626#endif
1627                         ENDIF
1628                      ENDIF
1629                   ENDIF
1630
1631!
1632!--                If required, carry out averaging along x
1633                   IF ( section(is,s_ind) == -1 )  THEN
1634
1635                      ALLOCATE( local_2d_l(nys:nyn,nzb_do:nzt_do) )
1636                      local_2d_l = 0.0_wp
1637                      ngp = ( nyn-nys+1 ) * ( nzt_do-nzb_do+1 )
1638!
1639!--                   First local averaging on the PE
1640                      DO  k = nzb_do, nzt_do
1641                         DO  j = nys, nyn
1642                            DO  i = nxl, nxr
1643                               local_2d_l(j,k) = local_2d_l(j,k) +             &
1644                                                 local_pf(i,j,k)
1645                            ENDDO
1646                         ENDDO
1647                      ENDDO
1648#if defined( __parallel )
1649!
1650!--                   Now do the averaging over all PEs along x
1651                      IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
1652                      CALL MPI_ALLREDUCE( local_2d_l(nys,nzb_do),                &
1653                                          local_2d(nys,nzb_do), ngp, MPI_REAL,   &
1654                                          MPI_SUM, comm1dx, ierr )
1655#else
1656                      local_2d = local_2d_l
1657#endif
1658                      local_2d = local_2d / ( nx + 1.0_wp )
1659
1660                      DEALLOCATE( local_2d_l )
1661
1662                   ELSE
1663!
1664!--                   Just store the respective section on the local array
1665!--                   (but only if it is available on this PE!)
1666                      IF ( section(is,s_ind) >= nxl  .AND.  section(is,s_ind) <= nxr ) &
1667                      THEN
1668                         local_2d = local_pf(section(is,s_ind),:,nzb_do:nzt_do)
1669                      ENDIF
1670
1671                   ENDIF
1672
1673#if defined( __parallel )
1674                   IF ( netcdf_data_format > 4 )  THEN
1675!
1676!--                   Output in netCDF4/HDF5 format.
1677!--                   Output only on those PEs where the respective cross
1678!--                   sections reside. Cross sections averaged along x are
1679!--                   output on the respective first PE along x (myidx=0).
1680                      IF ( ( section(is,s_ind) >= nxl  .AND.                       &
1681                             section(is,s_ind) <= nxr )  .OR.                      &
1682                           ( section(is,s_ind) == -1  .AND.  myidx == 0 ) )  THEN
1683#if defined( __netcdf )
1684!
1685!--                      For parallel output, all cross sections are first
1686!--                      stored here on a local array and will be written to the
1687!--                      output file afterwards to increase the performance.
1688                         DO  j = nys, nyn
1689                            DO  k = nzb_do, nzt_do
1690                               local_2d_sections_l(is,j,k) = local_2d(j,k)
1691                            ENDDO
1692                         ENDDO
1693#endif
1694                      ENDIF
1695
1696                   ELSE
1697
1698                      IF ( data_output_2d_on_each_pe )  THEN
1699!
1700!--                      Output of partial arrays on each PE. If the cross
1701!--                      section does not reside on the PE, output special
1702!--                      index values.
1703#if defined( __netcdf )
1704                         IF ( myid == 0 )  THEN
1705                            WRITE ( 23 )  time_since_reference_point,          &
1706                                          do2d_yz_time_count(av), av
1707                         ENDIF
1708#endif
1709                         DO  i = 0, io_blocks-1
1710                            IF ( i == io_group )  THEN
1711                               IF ( ( section(is,s_ind) >= nxl  .AND.          &
1712                                      section(is,s_ind) <= nxr )  .OR.         &
1713                                    ( section(is,s_ind) == -1  .AND.           &
1714                                      nxl-1 == -1 ) )                          &
1715                               THEN
1716                                  WRITE (23)  nys, nyn, nzb_do, nzt_do, nzb, nzt+1
1717                                  WRITE (23)  local_2d
1718                               ELSE
1719                                  WRITE (23)  -1, -1, -1, -1, -1, -1
1720                               ENDIF
1721                            ENDIF
1722#if defined( __parallel )
1723                            CALL MPI_BARRIER( comm2d, ierr )
1724#endif
1725                         ENDDO
1726
1727                      ELSE
1728!
1729!--                      PE0 receives partial arrays from all processors of the
1730!--                      respective cross section and outputs them. Here a
1731!--                      barrier has to be set, because otherwise
1732!--                      "-MPI- FATAL: Remote protocol queue full" may occur.
1733                         CALL MPI_BARRIER( comm2d, ierr )
1734
1735                         ngp = ( nyn-nys+1 ) * ( nzt_do-nzb_do+1 )
1736                         IF ( myid == 0 )  THEN
1737!
1738!--                         Local array can be relocated directly.
1739                            IF ( ( section(is,s_ind) >= nxl  .AND.             &
1740                                   section(is,s_ind) <= nxr )   .OR.           &
1741                                 ( section(is,s_ind) == -1  .AND.  nxl-1 == -1 ) ) &
1742                            THEN
1743                               total_2d(nys:nyn,nzb_do:nzt_do) = local_2d
1744                            ENDIF
1745!
1746!--                         Receive data from all other PEs.
1747                            DO  n = 1, numprocs-1
1748!
1749!--                            Receive index limits first, then array.
1750!--                            Index limits are received in arbitrary order from
1751!--                            the PEs.
1752                               CALL MPI_RECV( ind(1), 4, MPI_INTEGER,          &
1753                                              MPI_ANY_SOURCE, 0, comm2d,       &
1754                                              status, ierr )
1755!
1756!--                            Not all PEs have data for YZ-cross-section.
1757                               IF ( ind(1) /= -9999 )  THEN
1758                                  sender = status(MPI_SOURCE)
1759                                  DEALLOCATE( local_2d )
1760                                  ALLOCATE( local_2d(ind(1):ind(2),            &
1761                                                     ind(3):ind(4)) )
1762                                  CALL MPI_RECV( local_2d(ind(1),ind(3)), ngp, &
1763                                                 MPI_REAL, sender, 1, comm2d,  &
1764                                                 status, ierr )
1765                                  total_2d(ind(1):ind(2),ind(3):ind(4)) =      &
1766                                                                        local_2d
1767                               ENDIF
1768                            ENDDO
1769!
1770!--                         Relocate the local array for the next loop increment
1771                            DEALLOCATE( local_2d )
1772                            ALLOCATE( local_2d(nys:nyn,nzb_do:nzt_do) )
1773
1774#if defined( __netcdf )
1775                            nc_stat = NF90_PUT_VAR( id_set_yz(av),             &
1776                                                 id_var_do2d(av,ivar),           &
1777                                                 total_2d(0:ny,nzb_do:nzt_do), &
1778                            start = (/ is, 1, 1, do2d_yz_time_count(av) /),    &
1779                                       count = (/ 1, ny+1, nzt_do-nzb_do+1, 1 /) )
1780                            CALL netcdf_handle_error( 'data_output_2d', 61 )
1781#endif
1782
1783                         ELSE
1784!
1785!--                         If the cross section resides on the PE, send the
1786!--                         local index limits, otherwise send -9999 to PE0.
1787                            IF ( ( section(is,s_ind) >= nxl  .AND.              &
1788                                   section(is,s_ind) <= nxr )  .OR.             &
1789                                 ( section(is,s_ind) == -1  .AND.  nxl-1 == -1 ) ) &
1790                            THEN
1791                               ind(1) = nys; ind(2) = nyn
1792                               ind(3) = nzb_do;   ind(4) = nzt_do
1793                            ELSE
1794                               ind(1) = -9999; ind(2) = -9999
1795                               ind(3) = -9999; ind(4) = -9999
1796                            ENDIF
1797                            CALL MPI_SEND( ind(1), 4, MPI_INTEGER, 0, 0,       &
1798                                           comm2d, ierr )
1799!
1800!--                         If applicable, send data to PE0.
1801                            IF ( ind(1) /= -9999 )  THEN
1802                               CALL MPI_SEND( local_2d(nys,nzb_do), ngp,         &
1803                                              MPI_REAL, 0, 1, comm2d, ierr )
1804                            ENDIF
1805                         ENDIF
1806!
1807!--                      A barrier has to be set, because otherwise some PEs may
1808!--                      proceed too fast so that PE0 may receive wrong data on
1809!--                      tag 0
1810                         CALL MPI_BARRIER( comm2d, ierr )
1811                      ENDIF
1812
1813                   ENDIF
1814#else
1815#if defined( __netcdf )
1816                   nc_stat = NF90_PUT_VAR( id_set_yz(av),                   &
1817                                           id_var_do2d(av,ivar),              &
1818                                           local_2d(nys:nyn,nzb_do:nzt_do), &
1819                            start = (/ is, 1, 1, do2d_xz_time_count(av) /), &
1820                                           count = (/ 1, ny+1, nzt_do-nzb_do+1, 1 /) )
1821                   CALL netcdf_handle_error( 'data_output_2d', 452 )
1822#endif
1823#endif
1824
1825             END SELECT
1826
1827             is = is + 1
1828          ENDDO loop1
1829
1830!
1831!--       For parallel output, all data were collected before on a local array
1832!--       and are written now to the netcdf file. This must be done to increase
1833!--       the performance of the parallel output.
1834#if defined( __netcdf )
1835          IF ( netcdf_data_format > 4 )  THEN
1836
1837                SELECT CASE ( mode )
1838
1839                   CASE ( 'xy' )
1840                      IF ( two_d ) THEN
1841                         nis = 1
1842                         two_d = .FALSE.
1843                      ELSE
1844                         nis = ns
1845                      ENDIF
1846!
1847!--                   Do not output redundant ghost point data except for the
1848!--                   boundaries of the total domain.
1849!                      IF ( nxr == nx  .AND.  nyn /= ny )  THEN
1850!                         nc_stat = NF90_PUT_VAR( id_set_xy(av),                &
1851!                                                 id_var_do2d(av,ivar),           &
1852!                                                 local_2d_sections(nxl:nxr+1,  &
1853!                                                    nys:nyn,1:nis),            &
1854!                                                 start = (/ nxl+1, nys+1, 1,   &
1855!                                                    do2d_xy_time_count(av) /), &
1856!                                                 count = (/ nxr-nxl+2,         &
1857!                                                            nyn-nys+1, nis, 1  &
1858!                                                          /) )
1859!                      ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
1860!                         nc_stat = NF90_PUT_VAR( id_set_xy(av),                &
1861!                                                 id_var_do2d(av,ivar),           &
1862!                                                 local_2d_sections(nxl:nxr,    &
1863!                                                    nys:nyn+1,1:nis),          &
1864!                                                 start = (/ nxl+1, nys+1, 1,   &
1865!                                                    do2d_xy_time_count(av) /), &
1866!                                                 count = (/ nxr-nxl+1,         &
1867!                                                            nyn-nys+2, nis, 1  &
1868!                                                          /) )
1869!                      ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
1870!                         nc_stat = NF90_PUT_VAR( id_set_xy(av),                &
1871!                                                 id_var_do2d(av,ivar),           &
1872!                                                 local_2d_sections(nxl:nxr+1,  &
1873!                                                    nys:nyn+1,1:nis),          &
1874!                                                 start = (/ nxl+1, nys+1, 1,   &
1875!                                                    do2d_xy_time_count(av) /), &
1876!                                                 count = (/ nxr-nxl+2,         &
1877!                                                            nyn-nys+2, nis, 1  &
1878!                                                          /) )
1879!                      ELSE
1880                         nc_stat = NF90_PUT_VAR( id_set_xy(av),                &
1881                                                 id_var_do2d(av,ivar),           &
1882                                                 local_2d_sections(nxl:nxr,    &
1883                                                    nys:nyn,1:nis),            &
1884                                                 start = (/ nxl+1, nys+1, 1,   &
1885                                                    do2d_xy_time_count(av) /), &
1886                                                 count = (/ nxr-nxl+1,         &
1887                                                            nyn-nys+1, nis, 1  &
1888                                                          /) )
1889!                      ENDIF   
1890
1891                      CALL netcdf_handle_error( 'data_output_2d', 55 )
1892
1893                   CASE ( 'xz' )
1894!
1895!--                   First, all PEs get the information of all cross-sections.
1896!--                   Then the data are written to the output file by all PEs
1897!--                   while NF90_COLLECTIVE is set in subroutine
1898!--                   define_netcdf_header. Although redundant information are
1899!--                   written to the output file in that case, the performance
1900!--                   is significantly better compared to the case where only
1901!--                   the first row of PEs in x-direction (myidx = 0) is given
1902!--                   the output while NF90_INDEPENDENT is set.
1903                      IF ( npey /= 1 )  THEN
1904                         
1905#if defined( __parallel )
1906!
1907!--                      Distribute data over all PEs along y
1908                         ngp = ( nxr-nxl+1 ) * ( nzt_do-nzb_do+1 ) * ns
1909                         IF ( collective_wait ) CALL MPI_BARRIER( comm2d, ierr )
1910                         CALL MPI_ALLREDUCE( local_2d_sections_l(nxl,1,nzb_do),  &
1911                                             local_2d_sections(nxl,1,nzb_do),    &
1912                                             ngp, MPI_REAL, MPI_SUM, comm1dy,  &
1913                                             ierr )
1914#else
1915                         local_2d_sections = local_2d_sections_l
1916#endif
1917                      ENDIF
1918!
1919!--                   Do not output redundant ghost point data except for the
1920!--                   boundaries of the total domain.
1921!                      IF ( nxr == nx )  THEN
1922!                         nc_stat = NF90_PUT_VAR( id_set_xz(av),                &
1923!                                             id_var_do2d(av,ivar),               &
1924!                                             local_2d_sections(nxl:nxr+1,1:ns, &
1925!                                                nzb_do:nzt_do),                &
1926!                                             start = (/ nxl+1, 1, 1,           &
1927!                                                do2d_xz_time_count(av) /),     &
1928!                                             count = (/ nxr-nxl+2, ns, nzt_do-nzb_do+1,  &
1929!                                                        1 /) )
1930!                      ELSE
1931                         nc_stat = NF90_PUT_VAR( id_set_xz(av),                &
1932                                             id_var_do2d(av,ivar),               &
1933                                             local_2d_sections(nxl:nxr,1:ns,   &
1934                                                nzb_do:nzt_do),                &
1935                                             start = (/ nxl+1, 1, 1,           &
1936                                                do2d_xz_time_count(av) /),     &
1937                                             count = (/ nxr-nxl+1, ns, nzt_do-nzb_do+1,  &
1938                                                1 /) )
1939!                      ENDIF
1940
1941                      CALL netcdf_handle_error( 'data_output_2d', 57 )
1942
1943                   CASE ( 'yz' )
1944!
1945!--                   First, all PEs get the information of all cross-sections.
1946!--                   Then the data are written to the output file by all PEs
1947!--                   while NF90_COLLECTIVE is set in subroutine
1948!--                   define_netcdf_header. Although redundant information are
1949!--                   written to the output file in that case, the performance
1950!--                   is significantly better compared to the case where only
1951!--                   the first row of PEs in y-direction (myidy = 0) is given
1952!--                   the output while NF90_INDEPENDENT is set.
1953                      IF ( npex /= 1 )  THEN
1954
1955#if defined( __parallel )
1956!
1957!--                      Distribute data over all PEs along x
1958                         ngp = ( nyn-nys+1 ) * ( nzt-nzb + 2 ) * ns
1959                         IF ( collective_wait ) CALL MPI_BARRIER( comm2d, ierr )
1960                         CALL MPI_ALLREDUCE( local_2d_sections_l(1,nys,nzb_do),  &
1961                                             local_2d_sections(1,nys,nzb_do),    &
1962                                             ngp, MPI_REAL, MPI_SUM, comm1dx,  &
1963                                             ierr )
1964#else
1965                         local_2d_sections = local_2d_sections_l
1966#endif
1967                      ENDIF
1968!
1969!--                   Do not output redundant ghost point data except for the
1970!--                   boundaries of the total domain.
1971!                      IF ( nyn == ny )  THEN
1972!                         nc_stat = NF90_PUT_VAR( id_set_yz(av),                &
1973!                                             id_var_do2d(av,ivar),               &
1974!                                             local_2d_sections(1:ns,           &
1975!                                                nys:nyn+1,nzb_do:nzt_do),      &
1976!                                             start = (/ 1, nys+1, 1,           &
1977!                                                do2d_yz_time_count(av) /),     &
1978!                                             count = (/ ns, nyn-nys+2,         &
1979!                                                        nzt_do-nzb_do+1, 1 /) )
1980!                      ELSE
1981                         nc_stat = NF90_PUT_VAR( id_set_yz(av),                &
1982                                             id_var_do2d(av,ivar),               &
1983                                             local_2d_sections(1:ns,nys:nyn,   &
1984                                                nzb_do:nzt_do),                &
1985                                             start = (/ 1, nys+1, 1,           &
1986                                                do2d_yz_time_count(av) /),     &
1987                                             count = (/ ns, nyn-nys+1,         &
1988                                                        nzt_do-nzb_do+1, 1 /) )
1989!                      ENDIF
1990
1991                      CALL netcdf_handle_error( 'data_output_2d', 60 )
1992
1993                   CASE DEFAULT
1994                      message_string = 'unknown cross-section: ' // TRIM( mode )
1995                      CALL message( 'data_output_2d', 'PA0180', 1, 2, 0, 6, 0 )
1996
1997                END SELECT                     
1998
1999          ENDIF
2000#endif
2001       ENDIF
2002
2003       ivar = ivar + 1
2004       l = MAX( 2, LEN_TRIM( do2d(av,ivar) ) )
2005       do2d_mode = do2d(av,ivar)(l-1:l)
2006
2007    ENDDO
2008
2009!
2010!-- Deallocate temporary arrays.
2011    IF ( ALLOCATED( level_z ) )  DEALLOCATE( level_z )
2012    IF ( netcdf_data_format > 4 )  THEN
2013       DEALLOCATE( local_pf, local_2d, local_2d_sections )
2014       IF( mode == 'xz' .OR. mode == 'yz' ) DEALLOCATE( local_2d_sections_l )
2015    ENDIF
2016#if defined( __parallel )
2017    IF ( .NOT.  data_output_2d_on_each_pe  .AND.  myid == 0 )  THEN
2018       DEALLOCATE( total_2d )
2019    ENDIF
2020#endif
2021
2022!
2023!-- Close plot output file.
2024    file_id = 20 + s_ind
2025
2026    IF ( data_output_2d_on_each_pe )  THEN
2027       DO  i = 0, io_blocks-1
2028          IF ( i == io_group )  THEN
2029             CALL close_file( file_id )
2030          ENDIF
2031#if defined( __parallel )
2032          CALL MPI_BARRIER( comm2d, ierr )
2033#endif
2034       ENDDO
2035    ELSE
2036       IF ( myid == 0 )  CALL close_file( file_id )
2037    ENDIF
2038
2039    CALL cpu_log( log_point(3), 'data_output_2d', 'stop' )
2040
2041    IF ( debug_output_timestep )  CALL debug_message( 'data_output_2d', 'end' )
2042
2043
2044 END SUBROUTINE data_output_2d
Note: See TracBrowser for help on using the repository browser.