source: palm/trunk/SOURCE/sum_up_3d_data.f90 @ 667

Last change on this file since 667 was 667, checked in by suehring, 13 years ago

summary:


Gryschka:

  • Coupling with different resolution and different numbers of PEs in ocean and atmosphere is available
  • Exchange of u and v from ocean surface to atmosphere surface
  • Mirror boundary condition for u and v at the bottom are replaced by dirichlet boundary conditions
  • Inflow turbulence is now defined by flucuations around spanwise mean
  • Bugfixes for cyclic_fill and constant_volume_flow

Suehring:

  • New advection added ( Wicker and Skamarock 5th order ), therefore:
    • New module advec_ws.f90
    • Modified exchange of ghost boundaries.
    • Modified evaluation of turbulent fluxes
    • New index bounds nxlg, nxrg, nysg, nyng

advec_ws.f90


Advection scheme for scalars and momentum using the flux formulation of
Wicker and Skamarock 5th order.
Additionally the module contains of a routine using for initialisation and
steering of the statical evaluation. The computation of turbulent fluxes takes
place inside the advection routines.
In case of vector architectures Dirichlet and Radiation boundary conditions are
outstanding and not available. Furthermore simulations within topography are
not possible so far. A further routine local_diss_ij is available and is used
if a control of dissipative fluxes is desired.

check_parameters.f90


Exchange of parameters between ocean and atmosphere via PE0
Check for illegal combination of ws-scheme and timestep scheme.
Check for topography and ws-scheme.
Check for not cyclic boundary conditions in combination with ws-scheme and
loop_optimization = 'vector'.
Check for call_psolver_at_all_substeps and ws-scheme for momentum_advec.

Different processor/grid topology in atmosphere and ocean is now allowed!
Bugfixes in checking for conserve_volume_flow_mode.

exchange_horiz.f90


Dynamic exchange of ghost points with nbgp_local to ensure that no useless
ghost points exchanged in case of multigrid. type_yz(0) and type_xz(0) used for
normal grid, the remaining types used for the several grid levels.
Exchange is done via MPI-Vectors with a dynamic value of ghost points which
depend on the advection scheme. Exchange of left and right PEs is 10% faster
with MPI-Vectors than without.

flow_statistics.f90


When advection is computed with ws-scheme, turbulent fluxes are already
computed in the respective advection routines and buffered in arrays
sums_xxxx_ws_l(). This is due to a consistent treatment of statistics
with the numerics and to avoid unphysical kinks near the surface. So some if-
requests has to be done to dicern between fluxes from ws-scheme other advection
schemes. Furthermore the computation of z_i is only done if the heat flux
exceeds a minimum value. This affects only simulations of a neutral boundary
layer and is due to reasons of computations in the advection scheme.

inflow_turbulence.f90


Using nbgp recycling planes for a better resolution of the turbulent flow near
the inflow.

init_grid.f90


Definition of new array bounds nxlg, nxrg, nysg, nyng on each PE.
Furthermore the allocation of arrays and steering of loops is done with these
parameters. Call of exchange_horiz are modified.
In case of dirichlet bounday condition at the bottom zu(0)=0.0
dzu_mg has to be set explicitly for a equally spaced grid near bottom.
ddzu_pres added to use a equally spaced grid near bottom.

init_pegrid.f90


Moved determination of target_id's from init_coupling
Determination of parameters needed for coupling (coupling_topology, ngp_a, ngp_o)
with different grid/processor-topology in ocean and atmosphere

Adaption of ngp_xy, ngp_y to a dynamic number of ghost points.
The maximum_grid_level changed from 1 to 0. 0 is the normal grid, 1 to
maximum_grid_level the grids for multigrid, in which 0 and 1 are normal grids.
This distinction is due to reasons of data exchange and performance for the
normal grid and grids in poismg.
The definition of MPI-Vectors adapted to a dynamic numer of ghost points.
New MPI-Vectors for data exchange between left and right boundaries added.
This is due to reasons of performance (10% faster).

ATTENTION: nnz_x undefined problem still has to be solved!!!!!!!!
TEST OUTPUT (TO BE REMOVED) logging mpi2 ierr values

parin.f90


Steering parameter dissipation_control added in inipar.

Makefile


Module advec_ws added.

Modules


Removed u_nzb_p1_for_vfc and v_nzb_p1_for_vfc

For coupling with different resolution in ocean and atmophere:
+nx_a, +nx_o, ny_a, +ny_o, ngp_a, ngp_o, +total_2d_o, +total_2d_a,
+coupling_topology

Buffer arrays for the left sided advective fluxes added in arrays_3d.
+flux_s_u, +flux_s_v, +flux_s_w, +diss_s_u, +diss_s_v, +diss_s_w,
+flux_s_pt, +diss_s_pt, +flux_s_e, +diss_s_e, +flux_s_q, +diss_s_q,
+flux_s_sa, +diss_s_sa
3d arrays for dissipation control added. (only necessary for vector arch.)
+var_x, +var_y, +var_z, +gamma_x, +gamma_y, +gamma_z
Default of momentum_advec and scalar_advec changed to 'ws-scheme' .
+exchange_mg added in control_parameters to steer the data exchange.
Parameters +nbgp, +nxlg, +nxrg, +nysg, +nyng added in indices.
flag array +boundary_flags added in indices to steer the degradation of order
of the advective fluxes when non-cyclic boundaries are used.
MPI-datatypes +type_y, +type_y_int and +type_yz for data_exchange added in
pegrid.
+sums_wsus_ws_l, +sums_wsvs_ws_l, +sums_us2_ws_l, +sums_vs2_ws_l,
+sums_ws2_ws_l, +sums_wspts_ws_l, +sums_wssas_ws_l, +sums_wsqs_ws_l
and +weight_substep added in statistics to steer the statistical evaluation
of turbulent fluxes in the advection routines.
LOGICALS +ws_scheme_sca and +ws_scheme_mom added to get a better performance
in prognostic_equations.
LOGICAL +dissipation_control control added to steer numerical dissipation
in ws-scheme.

Changed length of string run_description_header

pres.f90


New allocation of tend when ws-scheme and multigrid is used. This is due to
reasons of perforance of the data_exchange. The same is done with p after
poismg is called.
nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng when no
multigrid is used. Calls of exchange_horiz are modified.

bugfix: After pressure correction no volume flow correction in case of
non-cyclic boundary conditions
(has to be done only before pressure correction)

Call of SOR routine is referenced with ddzu_pres.

prognostic_equations.f90


Calls of the advection routines with WS5 added.
Calls of ws_statistics added to set the statistical arrays to zero after each
time step.

advec_particles.f90


Declaration of de_dx, de_dy, de_dz adapted to additional ghost points.
Furthermore the calls of exchange_horiz were modified.

asselin_filter.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng

average_3d_data.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng

boundary_conds.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng
Removed mirror boundary conditions for u and v at the bottom in case of
ibc_uv_b == 0. Instead, dirichelt boundary conditions (u=v=0) are set
in init_3d_model

calc_liquid_water_content.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng

calc_spectra.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng for
allocation of tend.

check_open.f90


Output of total array size was adapted to nbgp.

data_output_2d.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng in loops and
allocation of arrays local_2d and total_2d.
Calls of exchange_horiz are modified.

data_output_2d.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng in loops and
allocation of arrays. Calls of exchange_horiz are modified.
Skip-value skip_do_avs changed to a dynamic adaption of ghost points.

data_output_mask.f90


Calls of exchange_horiz are modified.

diffusion_e.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng

diffusion_s.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng

diffusion_u.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng

diffusion_v.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng

diffusion_w.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng

diffusivities.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng

diffusivities.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng.
Calls of exchange_horiz are modified.

exchange_horiz_2d.f90


Dynamic exchange of ghost points with nbgp, which depends on the advection
scheme. Exchange between left and right PEs is now done with MPI-vectors.

global_min_max.f90


Adapting of the index arrays, because MINLOC assumes lowerbound
at 1 and not at nbgp.

init_3d_model.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng in loops and
allocation of arrays. Calls of exchange_horiz are modified.
Call ws_init to initialize arrays needed for statistical evaluation and
optimization when ws-scheme is used.
Initial volume flow is now calculated by using the variable hom_sum.
Therefore the correction of initial volume flow for non-flat topography
removed (removed u_nzb_p1_for_vfc and v_nzb_p1_for_vfc)
Changed surface boundary conditions for u and v in case of ibc_uv_b == 0 from
mirror bc to dirichlet boundary conditions (u=v=0), so that k=nzb is
representative for the height z0

Bugfix: type conversion of '1' to 64bit for the MAX function (ngp_3d_inner)

init_coupling.f90


determination of target_id's moved to init_pegrid

init_pt_anomaly.f90


Call of exchange_horiz are modified.

init_rankine.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng.
Calls of exchange_horiz are modified.

init_slope.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng.

header.f90


Output of advection scheme.

poismg.f90


Calls of exchange_horiz are modified.

prandtl_fluxes.f90


Changed surface boundary conditions for u and v from mirror bc to dirichelt bc,
therefore u(uzb,:,:) and v(nzb,:,:) is now representative for the height z0
nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng

production_e.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng

read_3d_binary.f90


+/- 1 replaced with +/- nbgp when swapping and allocating variables.

sor.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng.
Call of exchange_horiz are modified.
bug removed in declaration of ddzw(), nz replaced by nzt+1

subsidence.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng.

sum_up_3d_data.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng.

surface_coupler.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng in
MPI_SEND() and MPI_RECV.
additional case for nonequivalent processor and grid topopolgy in ocean and
atmosphere added (coupling_topology = 1)

Added exchange of u and v from Ocean to Atmosphere

time_integration.f90


Calls of exchange_horiz are modified.
Adaption to slooping surface.

timestep.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng.

user_3d_data_averaging.f90, user_data_output_2d.f90, user_data_output_3d.f90,
user_actions.f90, user_init.f90, user_init_plant_canopy.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng.

user_read_restart_data.f90


Allocation with nbgp.

wall_fluxes.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng.

write_compressed.f90


Array bounds and nx, ny adapted with nbgp.

sor.f90


bug removed in declaration of ddzw(), nz replaced by nzt+1

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