source: palm/tags/release-3.7/SOURCE/sum_up_3d_data.f90 @ 1709

Last change on this file since 1709 was 392, checked in by raasch, 15 years ago

New:
---

Adapted for machine lck
(mrun, mbuild, subjob)

bc_lr/bc_ns in most subroutines replaced by LOGICAL variables bc_lr_cyc,
bc_ns_cyc for speed optimization
(check_parameters, diffusion_u, diffusion_v, diffusion_w, modules)

Additional timestep criterion in case of simulations with plant canopy (timestep)

Check for illegal entries in section_xy|xz|yz that exceed nz+1|ny+1|nx+1
(check_parameters)

Clipping of dvrp output implemented. Default colourtable for particles
implemented, particle attributes (color, dvrp_size) can be set with new
parameters particle_color, particle_dvrpsize, color_interval,
dvrpsize_interval (init_dvrp, data_output_dvrp, modules, user_data_output_dvrp).
Slicer attributes (dvrp) are set with new routine set_slicer_attributes_dvrp
and are controlled with existing parameters slicer_range_limits.
(set_slicer_attributes_dvrp)

Ocean atmosphere coupling allows to use independent precursor runs in order
to account for different spin-up times. The time when coupling has to be
started is given by new inipar parameter coupling_start_time. The precursor
ocean run has to be started using new mrun option "-y" in order to add
appendix "_O" to all output files.
(check_for_restart, check_parameters, data_output_2d, data_output_3d,
data_output_profiles, data_output_ptseries, data_output_spectra,
data_output_tseries, header, init_coupling, modules, mrun,
parin, read_var_list, surface_coupler, time_integration, write_var_list)

Polygon reduction for topography and ground plate isosurface. Reduction level
for buildings can be chosen with parameter cluster_size. (init_dvrp)

External pressure gradient (check_parameters, header, init_3d_model, modules,
parin, prognostic_equations, read_var_list, write_var_list)

New topography case 'single_street_canyon' (header, init_grid, modules, parin,
read_var_list, user_check_parameters, user_header, user_init_grid, write_var_list)

Option to predefine a target bulk velocity for conserve_volume_flow
(check_parameters, header, init_3d_model, modules, parin, read_var_list,
write_var_list)

Option for user defined 2D data output in xy cross sections at z=nzb+1
(data_output_2d, user_data_output_2d)

xy cross section output of surface heatfluxes (latent, sensible)
(average_3d_data, check_parameters, data_output_2d, modules, read_3d_binary,
sum_up_3d_data, write_3d_binary)

average_3d_data, check_for_restart, check_parameters, data_output_2d, data_output_3d, data_output_dvrp, data_output_profiles, data_output_ptseries, data_output_spectra, data_output_tseries, init_coupling, init_dvrp, init_grid, init_3d_model, header, mbuild, modules, mrun, package_parin, parin, prognostic_equations, read_3d_binary, read_var_list, subjob, surface_coupler, timestep, time_integration, user_check_parameters, user_data_output_2d, user_data_output_dvrp, user_header, user_init_grid, write_3d_binary, write_var_list

New: set_particle_attributes, set_slicer_attributes_dvrp

Changed:


lcmuk changed to lc to avoid problems with Intel compiler on sgi-ice
(poisfft)

For extended NetCDF files, the updated title attribute includes an update of
time_average_text where appropriate. (netcdf)

In case of restart runs without extension, initial profiles are not written
to NetCDF-file anymore. (data_output_profiles, modules, read_var_list, write_var_list)

Small change in formatting of the message handling routine concering the output in the
job protocoll. (message)

initializing_actions='read_data_for_recycling' renamed to 'cyclic_fill', now
independent of turbulent_inflow (check_parameters, header, init_3d_model)

2 NetCDF error numbers changed. (data_output_3d)

A Link to the website appendix_a.html is printed for further information
about the possible errors. (message)

Temperature gradient criterion for estimating the boundary layer height
replaced by the gradient criterion of Sullivan et al. (1998). (flow_statistics)

NetCDF unit attribute in timeseries output in case of statistic regions added
(netcdf)

Output of NetCDF messages with aid of message handling routine.
(check_open, close_file, data_output_2d, data_output_3d,
data_output_profiles, data_output_ptseries, data_output_spectra,
data_output_tseries, netcdf, output_particles_netcdf)

Output of messages replaced by message handling routine.
(advec_particles, advec_s_bc, buoyancy, calc_spectra, check_for_restart,
check_open, coriolis, cpu_log, data_output_2d, data_output_3d, data_output_dvrp,
data_output_profiles, data_output_spectra, fft_xy, flow_statistics, header,
init_1d_model, init_3d_model, init_dvrp, init_grid, init_particles, init_pegrid,
netcdf, parin, plant_canopy_model, poisfft_hybrid, poismg, read_3d_binary,
read_var_list, surface_coupler, temperton_fft, timestep, user_actions,
user_data_output_dvrp, user_dvrp_coltab, user_init_grid, user_init_plant_canopy,
user_parin, user_read_restart_data, user_spectra )

Maximum number of tails is calculated from maximum number of particles and
skip_particles_for_tail (init_particles)

Value of vertical_particle_advection may differ for each particle group
(advec_particles, header, modules)

First constant in array den also defined as type double. (eqn_state_seawater)

Parameter dvrp_psize moved from particles_par to dvrp_graphics_par. (package_parin)

topography_grid_convention moved from userpar to inipar (check_parameters,
header, parin, read_var_list, user_check_parameters, user_header,
user_init_grid, user_parin, write_var_list)

Default value of grid_matching changed to strict.

Adjustments for runs on lcxt4 (necessary due to an software update on CRAY) and
for coupled runs on ibmy (mrun, subjob)

advec_particles, advec_s_bc, buoyancy, calc_spectra, check_for_restart, check_open, check_parameters, close_file, coriolis, cpu_log, data_output_2d, data_output_3d, data_output_dvrp, data_output_profiles, data_output_ptseries, data_output_spectra, data_output_tseries, eqn_state_seawater, fft_xy, flow_statistics, header, init_1d_model, init_3d_model, init_dvrp, init_grid, init_particles, init_pegrid, message, mrun, netcdf, output_particles_netcdf, package_parin, parin, plant_canopy_model, poisfft, poisfft_hybrid, poismg, read_3d_binary, read_var_list, sort_particles, subjob, user_check_parameters, user_header, user_init_grid, user_parin, surface_coupler, temperton_fft, timestep, user_actions, user_data_output_dvrp, user_dvrp_coltab, user_init_grid, user_init_plant_canopy, user_parin, user_read_restart_data, user_spectra, write_var_list

Errors:


Bugfix: Initial hydrostatic pressure profile in case of ocean runs is now
calculated in 5 iteration steps. (init_ocean)

Bugfix: wrong sign in buoyancy production of ocean part in case of not using
the reference density (only in 3D routine production_e) (production_e)

Bugfix: output of averaged 2d/3d quantities requires that an avaraging
interval has been set, respective error message is included (check_parameters)

Bugfix: Output on unit 14 only if requested by write_binary.
(user_last_actions)

Bugfix to avoid zero division by km_neutral (production_e)

Bugfix for extended NetCDF files: In order to avoid 'data mode' errors if
updated attributes are larger than their original size, NF90_PUT_ATT is called
in 'define mode' enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a
possible performance loss; an alternative strategy would be to ensure equal
attribute size in a job chain. (netcdf)

Bugfix: correction of initial volume flow for non-flat topography (init_3d_model)
Bugfix: zero initialization of arrays within buildings for 'cyclic_fill' (init_3d_model)

Bugfix: to_be_resorted => s_av for time-averaged scalars (data_output_2d, data_output_3d)

Bugfix: error in formatting the output (message)

Bugfix: avoid that ngp_2dh_s_inner becomes zero (init_3_model)

Typographical error: unit of wpt in dots_unit (modules)

Bugfix: error in check, if particles moved further than one subdomain length.
This check must not be applied for newly released particles. (advec_particles)

Bugfix: several tail counters are initialized, particle_tail_coordinates is
only written to file if its third index is > 0, arrays for tails are allocated
with a minimum size of 10 tails if there is no tail initially (init_particles,
advec_particles)

Bugfix: pressure included for profile output (check_parameters)

Bugfix: Type of count and count_rate changed to default INTEGER on NEC machines
(cpu_log)

Bugfix: output if particle time series only if particle advection is switched
on. (time_integration)

Bugfix: qsws was calculated in case of constant heatflux = .FALSE. (prandtl_fluxes)

Bugfix: averaging along z is not allowed for 2d quantities (e.g. u* and z0) (data_output_2d)

Typographical errors (netcdf)

If the inversion height calculated by the prerun is zero, inflow_damping_height
must be explicitly specified (init_3d_model)

Small bugfix concerning 3d 64bit netcdf output format (header)

Bugfix: dt_fixed removed from the restart file, because otherwise, no change
from a fixed to a variable timestep would be possible in restart runs.
(read_var_list, write_var_list)

Bugfix: initial setting of time_coupling in coupled restart runs (time_integration)

advec_particles, check_parameters, cpu_log, data_output_2d, data_output_3d, header, init_3d_model, init_particles, init_ocean, modules, netcdf, prandtl_fluxes, production_e, read_var_list, time_integration, user_last_actions, write_var_list

  • Property svn:keywords set to Id
File size: 13.7 KB
Line 
1 SUBROUTINE sum_up_3d_data
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: sum_up_3d_data.f90 392 2009-09-24 10:39:14Z maronga $
11!
12! 2009-08-25 08:35:52Z maronga
13! +shf*, qsws*
14!
15! 96 2007-06-04 08:07:41Z raasch
16! +sum-up of density and salinity
17!
18! 72 2007-03-19 08:20:46Z raasch
19! +sum-up of precipitation rate and roughness length (prr*, z0*)
20!
21! RCS Log replace by Id keyword, revision history cleaned up
22!
23! Revision 1.1  2006/02/23 12:55:23  raasch
24! Initial revision
25!
26!
27! Description:
28! ------------
29! Sum-up the values of 3d-arrays. The real averaging is later done in routine
30! average_3d_data.
31!------------------------------------------------------------------------------!
32
33    USE arrays_3d
34    USE averaging
35    USE cloud_parameters
36    USE control_parameters
37    USE cpulog
38    USE indices
39    USE interfaces
40    USE particle_attributes
41
42    IMPLICIT NONE
43
44    INTEGER ::  i, ii, j, k, n, psi
45
46    REAL    ::  mean_r, s_r3, s_r4
47
48
49    CALL cpu_log (log_point(34),'sum_up_3d_data','start')
50
51!
52!-- Allocate and initialize the summation arrays if called for the very first
53!-- time or the first time after average_3d_data has been called
54!-- (some or all of the arrays may have been already allocated
55!-- in read_3d_binary)
56    IF ( average_count_3d == 0 )  THEN
57
58       DO  ii = 1, doav_n
59
60          SELECT CASE ( TRIM( doav(ii) ) )
61
62             CASE ( 'e' )
63                IF ( .NOT. ALLOCATED( e_av ) )  THEN
64                   ALLOCATE( e_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
65                ENDIF
66                e_av = 0.0
67
68             CASE ( 'lwp*' )
69                IF ( .NOT. ALLOCATED( lwp_av ) )  THEN
70                   ALLOCATE( lwp_av(nys-1:nyn+1,nxl-1:nxr+1) )
71                ENDIF
72                lwp_av = 0.0
73
74             CASE ( 'p' )
75                IF ( .NOT. ALLOCATED( p_av ) )  THEN
76                   ALLOCATE( p_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
77                ENDIF
78                p_av = 0.0
79
80             CASE ( 'pc' )
81                IF ( .NOT. ALLOCATED( pc_av ) )  THEN
82                   ALLOCATE( pc_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
83                ENDIF
84                pc_av = 0.0
85
86             CASE ( 'pr' )
87                IF ( .NOT. ALLOCATED( pr_av ) )  THEN
88                   ALLOCATE( pr_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
89                ENDIF
90                pr_av = 0.0
91
92             CASE ( 'prr*' )
93                IF ( .NOT. ALLOCATED( precipitation_rate_av ) )  THEN
94                   ALLOCATE( precipitation_rate_av(nys-1:nyn+1,nxl-1:nxr+1) )
95                ENDIF
96                precipitation_rate_av = 0.0
97
98             CASE ( 'pt' )
99                IF ( .NOT. ALLOCATED( pt_av ) )  THEN
100                   ALLOCATE( pt_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
101                ENDIF
102                pt_av = 0.0
103
104             CASE ( 'q' )
105                IF ( .NOT. ALLOCATED( q_av ) )  THEN
106                   ALLOCATE( q_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
107                ENDIF
108                q_av = 0.0
109
110             CASE ( 'ql' )
111                IF ( .NOT. ALLOCATED( ql_av ) )  THEN
112                   ALLOCATE( ql_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
113                ENDIF
114                ql_av = 0.0
115
116             CASE ( 'ql_c' )
117                IF ( .NOT. ALLOCATED( ql_c_av ) )  THEN
118                   ALLOCATE( ql_c_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
119                ENDIF
120                ql_c_av = 0.0
121
122             CASE ( 'ql_v' )
123                IF ( .NOT. ALLOCATED( ql_v_av ) )  THEN
124                   ALLOCATE( ql_v_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
125                ENDIF
126                ql_v_av = 0.0
127
128             CASE ( 'ql_vp' )
129                IF ( .NOT. ALLOCATED( ql_vp_av ) )  THEN
130                   ALLOCATE( ql_vp_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
131                ENDIF
132                ql_vp_av = 0.0
133
134             CASE ( 'qsws*' )
135                IF ( .NOT. ALLOCATED( qsws_av ) )  THEN
136                   ALLOCATE( qsws_av(nys-1:nyn+1,nxl-1:nxr+1) )
137                ENDIF
138                qsws_av = 0.0
139
140             CASE ( 'qv' )
141                IF ( .NOT. ALLOCATED( qv_av ) )  THEN
142                   ALLOCATE( qv_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
143                ENDIF
144                qv_av = 0.0
145
146             CASE ( 'rho' )
147                IF ( .NOT. ALLOCATED( rho_av ) )  THEN
148                   ALLOCATE( rho_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
149                ENDIF
150                rho_av = 0.0
151
152             CASE ( 's' )
153                IF ( .NOT. ALLOCATED( s_av ) )  THEN
154                   ALLOCATE( s_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
155                ENDIF
156                s_av = 0.0
157
158             CASE ( 'sa' )
159                IF ( .NOT. ALLOCATED( sa_av ) )  THEN
160                   ALLOCATE( sa_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
161                ENDIF
162                sa_av = 0.0
163
164             CASE ( 'shf*' )
165                IF ( .NOT. ALLOCATED( shf_av ) )  THEN
166                   ALLOCATE( shf_av(nys-1:nyn+1,nxl-1:nxr+1) )
167                ENDIF
168                shf_av = 0.0
169
170             CASE ( 't*' )
171                IF ( .NOT. ALLOCATED( ts_av ) )  THEN
172                   ALLOCATE( ts_av(nys-1:nyn+1,nxl-1:nxr+1) )
173                ENDIF
174                ts_av = 0.0
175
176             CASE ( 'u' )
177                IF ( .NOT. ALLOCATED( u_av ) )  THEN
178                   ALLOCATE( u_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
179                ENDIF
180                u_av = 0.0
181
182             CASE ( 'u*' )
183                IF ( .NOT. ALLOCATED( us_av ) )  THEN
184                   ALLOCATE( us_av(nys-1:nyn+1,nxl-1:nxr+1) )
185                ENDIF
186                us_av = 0.0
187
188             CASE ( 'v' )
189                IF ( .NOT. ALLOCATED( v_av ) )  THEN
190                   ALLOCATE( v_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
191                ENDIF
192                v_av = 0.0
193
194             CASE ( 'vpt' )
195                IF ( .NOT. ALLOCATED( vpt_av ) )  THEN
196                   ALLOCATE( vpt_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
197                ENDIF
198                vpt_av = 0.0
199
200             CASE ( 'w' )
201                IF ( .NOT. ALLOCATED( w_av ) )  THEN
202                   ALLOCATE( w_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
203                ENDIF
204                w_av = 0.0
205
206             CASE ( 'z0*' )
207                IF ( .NOT. ALLOCATED( z0_av ) )  THEN
208                   ALLOCATE( z0_av(nys-1:nyn+1,nxl-1:nxr+1) )
209                ENDIF
210                z0_av = 0.0
211
212             CASE DEFAULT
213!
214!--             User-defined quantity
215                CALL user_3d_data_averaging( 'allocate', doav(ii) )
216
217          END SELECT
218
219       ENDDO
220
221    ENDIF
222
223!
224!-- Loop of all variables to be averaged.
225    DO  ii = 1, doav_n
226
227!
228!--    Store the array chosen on the temporary array.
229       SELECT CASE ( TRIM( doav(ii) ) )
230
231          CASE ( 'e' )
232             DO  i = nxl-1, nxr+1
233                DO  j = nys-1, nyn+1
234                   DO  k = nzb, nzt+1
235                      e_av(k,j,i) = e_av(k,j,i) + e(k,j,i)
236                   ENDDO
237                ENDDO
238             ENDDO
239
240          CASE ( 'lwp*' )
241             DO  i = nxl-1, nxr+1
242                DO  j = nys-1, nyn+1
243                   lwp_av(j,i) = lwp_av(j,i) + SUM( ql(nzb:nzt,j,i) * &
244                                                    dzw(1:nzt+1) )
245                ENDDO
246             ENDDO
247
248          CASE ( 'p' )
249             DO  i = nxl-1, nxr+1
250                DO  j = nys-1, nyn+1
251                   DO  k = nzb, nzt+1
252                      p_av(k,j,i) = p_av(k,j,i) + p(k,j,i)
253                   ENDDO
254                ENDDO
255             ENDDO
256
257          CASE ( 'pc' )
258             DO  i = nxl, nxr
259                DO  j = nys, nyn
260                   DO  k = nzb, nzt+1
261                      pc_av(k,j,i) = pc_av(k,j,i) + prt_count(k,j,i)
262                   ENDDO
263                ENDDO
264             ENDDO
265
266          CASE ( 'pr' )
267             DO  i = nxl, nxr
268                DO  j = nys, nyn
269                   DO  k = nzb, nzt+1
270                      psi = prt_start_index(k,j,i)
271                      s_r3 = 0.0
272                      s_r4 = 0.0
273                      DO  n = psi, psi+prt_count(k,j,i)-1
274                         s_r3 = s_r3 + particles(n)%radius**3
275                         s_r4 = s_r4 + particles(n)%radius**4
276                      ENDDO
277                      IF ( s_r3 /= 0.0 )  THEN
278                         mean_r = s_r4 / s_r3
279                      ELSE
280                         mean_r = 0.0
281                      ENDIF
282                      pr_av(k,j,i) = pr_av(k,j,i) + mean_r
283                   ENDDO
284                ENDDO
285             ENDDO
286
287          CASE ( 'pr*' )
288             DO  i = nxl-1, nxr+1
289                DO  j = nys-1, nyn+1
290                   precipitation_rate_av(j,i) = precipitation_rate_av(j,i) + &
291                                                precipitation_rate(j,i)
292                ENDDO
293             ENDDO
294
295          CASE ( 'pt' )
296             IF ( .NOT. cloud_physics ) THEN
297                DO  i = nxl-1, nxr+1
298                   DO  j = nys-1, nyn+1
299                      DO  k = nzb, nzt+1
300                         pt_av(k,j,i) = pt_av(k,j,i) + pt(k,j,i)
301                      ENDDO
302                   ENDDO
303                ENDDO
304             ELSE
305                DO  i = nxl-1, nxr+1
306                   DO  j = nys-1, nyn+1
307                      DO  k = nzb, nzt+1
308                         pt_av(k,j,i) = pt_av(k,j,i) + pt(k,j,i) + l_d_cp * &
309                                                       pt_d_t(k) * ql(k,j,i)
310                      ENDDO
311                   ENDDO
312                ENDDO
313             ENDIF
314
315          CASE ( 'q' )
316             DO  i = nxl-1, nxr+1
317                DO  j = nys-1, nyn+1
318                   DO  k = nzb, nzt+1
319                      q_av(k,j,i) = q_av(k,j,i) + q(k,j,i)
320                   ENDDO
321                ENDDO
322             ENDDO
323             
324          CASE ( 'ql' )
325             DO  i = nxl-1, nxr+1
326                DO  j = nys-1, nyn+1
327                   DO  k = nzb, nzt+1
328                      ql_av(k,j,i) = ql_av(k,j,i) + ql(k,j,i)
329                   ENDDO
330                ENDDO
331             ENDDO
332
333          CASE ( 'ql_c' )
334             DO  i = nxl-1, nxr+1
335                DO  j = nys-1, nyn+1
336                   DO  k = nzb, nzt+1
337                      ql_c_av(k,j,i) = ql_c_av(k,j,i) + ql_c(k,j,i)
338                   ENDDO
339                ENDDO
340             ENDDO
341
342          CASE ( 'ql_v' )
343             DO  i = nxl-1, nxr+1
344                DO  j = nys-1, nyn+1
345                   DO  k = nzb, nzt+1
346                      ql_v_av(k,j,i) = ql_v_av(k,j,i) + ql_v(k,j,i)
347                   ENDDO
348                ENDDO
349             ENDDO
350
351          CASE ( 'ql_vp' )
352             DO  i = nxl-1, nxr+1
353                DO  j = nys-1, nyn+1
354                   DO  k = nzb, nzt+1
355                      ql_vp_av(k,j,i) = ql_vp_av(k,j,i) + ql_vp(k,j,i)
356                   ENDDO
357                ENDDO
358             ENDDO
359
360          CASE ( 'qv' )
361             DO  i = nxl-1, nxr+1
362                DO  j = nys-1, nyn+1
363                   DO  k = nzb, nzt+1
364                      qv_av(k,j,i) = qv_av(k,j,i) + q(k,j,i) - ql(k,j,i)
365                   ENDDO
366                ENDDO
367             ENDDO
368
369          CASE ( 'rho' )
370             DO  i = nxl-1, nxr+1
371                DO  j = nys-1, nyn+1
372                   DO  k = nzb, nzt+1
373                      rho_av(k,j,i) = rho_av(k,j,i) + rho(k,j,i)
374                   ENDDO
375                ENDDO
376             ENDDO
377             
378          CASE ( 's' )
379             DO  i = nxl-1, nxr+1
380                DO  j = nys-1, nyn+1
381                   DO  k = nzb, nzt+1
382                      s_av(k,j,i) = s_av(k,j,i) + q(k,j,i)
383                   ENDDO
384                ENDDO
385             ENDDO
386             
387          CASE ( 'sa' )
388             DO  i = nxl-1, nxr+1
389                DO  j = nys-1, nyn+1
390                   DO  k = nzb, nzt+1
391                      sa_av(k,j,i) = sa_av(k,j,i) + sa(k,j,i)
392                   ENDDO
393                ENDDO
394             ENDDO
395             
396          CASE ( 't*' )
397             DO  i = nxl-1, nxr+1
398                DO  j = nys-1, nyn+1
399                   ts_av(j,i) = ts_av(j,i) + ts(j,i)
400                ENDDO
401             ENDDO
402
403          CASE ( 'u' )
404             DO  i = nxl-1, nxr+1
405                DO  j = nys-1, nyn+1
406                   DO  k = nzb, nzt+1
407                      u_av(k,j,i) = u_av(k,j,i) + u(k,j,i)
408                   ENDDO
409                ENDDO
410             ENDDO
411
412          CASE ( 'u*' )
413             DO  i = nxl-1, nxr+1
414                DO  j = nys-1, nyn+1
415                   us_av(j,i) = us_av(j,i) + us(j,i)
416                ENDDO
417             ENDDO
418
419          CASE ( 'v' )
420             DO  i = nxl-1, nxr+1
421                DO  j = nys-1, nyn+1
422                   DO  k = nzb, nzt+1
423                      v_av(k,j,i) = v_av(k,j,i) + v(k,j,i)
424                   ENDDO
425                ENDDO
426             ENDDO
427
428          CASE ( 'vpt' )
429             DO  i = nxl-1, nxr+1
430                DO  j = nys-1, nyn+1
431                   DO  k = nzb, nzt+1
432                      vpt_av(k,j,i) = vpt_av(k,j,i) + vpt(k,j,i)
433                   ENDDO
434                ENDDO
435             ENDDO
436
437          CASE ( 'w' )
438             DO  i = nxl-1, nxr+1
439                DO  j = nys-1, nyn+1
440                   DO  k = nzb, nzt+1
441                      w_av(k,j,i) = w_av(k,j,i) + w(k,j,i)
442                   ENDDO
443                ENDDO
444             ENDDO
445
446          CASE ( 'z0*' )
447             DO  i = nxl-1, nxr+1
448                DO  j = nys-1, nyn+1
449                   z0_av(j,i) = z0_av(j,i) + z0(j,i)
450                ENDDO
451             ENDDO
452
453          CASE DEFAULT
454!
455!--          User-defined quantity
456             CALL user_3d_data_averaging( 'sum', doav(ii) )
457
458       END SELECT
459
460    ENDDO
461
462    CALL cpu_log (log_point(34),'sum_up_3d_data','stop','nobarrier')
463
464
465 END SUBROUTINE sum_up_3d_data
Note: See TracBrowser for help on using the repository browser.