source: palm/trunk/SOURCE/average_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: 7.9 KB
RevLine 
[1]1 SUBROUTINE average_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: average_3d_data.f90 667 2010-12-23 12:06:00Z suehring $
[77]11!
[392]12! 367 2009-08-25 08:35:52Z maronga
13! Added calculation of shf* and qsws*
14!
[98]15! 96 2007-06-04 08:07:41Z raasch
16! Averaging of density and salinity
17!
[77]18! 72 2007-03-19 08:20:46Z raasch
19! Averaging the precipitation rate and roughness length (prr*, z0*)
20!
[3]21! RCS Log replace by Id keyword, revision history cleaned up
22!
[1]23! Revision 1.1  2006/02/23 09:48:58  raasch
24! Initial revision
25!
26!
27! Description:
28! ------------
29! Time-averaging of 3d-data-arrays.
30!------------------------------------------------------------------------------!
31
32    USE arrays_3d
33    USE averaging
34    USE cloud_parameters
35    USE control_parameters
36    USE cpulog
37    USE indices
38    USE interfaces
39
40    IMPLICIT NONE
41
42    INTEGER ::  i, ii, j, k
43
44
45    CALL cpu_log (log_point(35),'average_3d_data','start')
46
47!
48!-- Check, if averaging is necessary
49    IF ( average_count_3d <= 1 )  RETURN
50
51!
52!-- Loop of all variables to be averaged.
53    DO  ii = 1, doav_n
54
55!
56!--    Store the array chosen on the temporary array.
57       SELECT CASE ( TRIM( doav(ii) ) )
58
59          CASE ( 'e' )
[667]60             DO  i = nxlg, nxrg
61                DO  j = nysg, nyng
[1]62                   DO  k = nzb, nzt+1
63                      e_av(k,j,i) = e_av(k,j,i) / REAL( average_count_3d )
64                   ENDDO
65                ENDDO
66             ENDDO
67
[354]68          CASE ( 'qsws*' )
[667]69             DO  i = nxlg, nxrg
70                DO  j = nysg, nyng
[354]71                   qsws_av(j,i) = qsws_av(j,i) / REAL( average_count_3d )
72                ENDDO
73             ENDDO
74
[1]75          CASE ( 'lwp*' )
[667]76             DO  i = nxlg, nxrg
77                DO  j = nysg, nyng
[1]78                   lwp_av(j,i) = lwp_av(j,i) / REAL( average_count_3d )
79                ENDDO
80             ENDDO
81
82          CASE ( 'p' )
[667]83             DO  i = nxlg, nxrg
84                DO  j = nysg, nyng
[1]85                   DO  k = nzb, nzt+1
86                      p_av(k,j,i) = p_av(k,j,i) / REAL( average_count_3d )
87                   ENDDO
88                ENDDO
89             ENDDO
90
91          CASE ( 'pc' )
92             DO  i = nxl, nxr
93                DO  j = nys, nyn
94                   DO  k = nzb, nzt+1
95                      pc_av(k,j,i) = pc_av(k,j,i) / REAL( average_count_3d )
96                   ENDDO
97                ENDDO
98             ENDDO
99
100          CASE ( 'pr' )
101             DO  i = nxl, nxr
102                DO  j = nys, nyn
103                   DO  k = nzb, nzt+1
104                      pr_av(k,j,i) = pr_av(k,j,i) / REAL( average_count_3d )
105                   ENDDO
106                ENDDO
107             ENDDO
108
[72]109          CASE ( 'prr*' )
[667]110             DO  i = nxlg, nxrg
111                DO  j = nysg, nyng
[72]112                   precipitation_rate_av(j,i) = precipitation_rate_av(j,i) / &
113                                                REAL( average_count_3d )
114                ENDDO
115             ENDDO
116
[1]117          CASE ( 'pt' )
[667]118             DO  i = nxlg, nxrg
119                DO  j = nysg, nyng
[1]120                   DO  k = nzb, nzt+1
121                      pt_av(k,j,i) = pt_av(k,j,i) / REAL( average_count_3d )
122                   ENDDO
123                ENDDO
124             ENDDO
125
126          CASE ( 'q' )
[667]127             DO  i = nxlg, nxrg
128                DO  j = nysg, nyng
[1]129                   DO  k = nzb, nzt+1
130                      q_av(k,j,i) = q_av(k,j,i) / REAL( average_count_3d )
131                   ENDDO
132                ENDDO
133             ENDDO
[367]134
[1]135          CASE ( 'ql' )
[667]136             DO  i = nxlg, nxrg
137                DO  j = nysg, nyng
[1]138                   DO  k = nzb, nzt+1
139                      ql_av(k,j,i) = ql_av(k,j,i) / REAL( average_count_3d )
140                   ENDDO
141                ENDDO
142             ENDDO
143
144          CASE ( 'ql_c' )
[667]145             DO  i = nxlg, nxrg
146                DO  j = nysg, nyng
[1]147                   DO  k = nzb, nzt+1
148                      ql_c_av(k,j,i) = ql_c_av(k,j,i) / REAL( average_count_3d )
149                   ENDDO
150                ENDDO
151             ENDDO
152
153          CASE ( 'ql_v' )
[667]154             DO  i = nxlg, nxrg
155                DO  j = nysg, nyng
[1]156                   DO  k = nzb, nzt+1
157                      ql_v_av(k,j,i) = ql_v_av(k,j,i) / REAL( average_count_3d )
158                   ENDDO
159                ENDDO
160             ENDDO
161
162          CASE ( 'ql_vp' )
[667]163             DO  i = nxlg, nxrg
164                DO  j = nysg, nyng
[1]165                   DO  k = nzb, nzt+1
166                      ql_vp_av(k,j,i) = ql_vp_av(k,j,i) / &
167                                        REAL( average_count_3d )
168                   ENDDO
169                ENDDO
170             ENDDO
171
172          CASE ( 'qv' )
[667]173             DO  i = nxlg, nxrg
174                DO  j = nysg, nyng
[1]175                   DO  k = nzb, nzt+1
176                      qv_av(k,j,i) = qv_av(k,j,i) / REAL( average_count_3d )
177                   ENDDO
178                ENDDO
179             ENDDO
[367]180
[96]181          CASE ( 'rho' )
[667]182             DO  i = nxlg, nxrg
183                DO  j = nysg, nyng
[96]184                   DO  k = nzb, nzt+1
185                      rho_av(k,j,i) = rho_av(k,j,i) / REAL( average_count_3d )
186                   ENDDO
187                ENDDO
188             ENDDO
[367]189
[1]190          CASE ( 's' )
[667]191             DO  i = nxlg, nxrg
192                DO  j = nysg, nyng
[1]193                   DO  k = nzb, nzt+1
194                      s_av(k,j,i) = s_av(k,j,i) / REAL( average_count_3d )
195                   ENDDO
196                ENDDO
197             ENDDO
[367]198
[96]199          CASE ( 'sa' )
[667]200             DO  i = nxlg, nxrg
201                DO  j = nysg, nyng
[96]202                   DO  k = nzb, nzt+1
203                      sa_av(k,j,i) = sa_av(k,j,i) / REAL( average_count_3d )
204                   ENDDO
205                ENDDO
206             ENDDO
[367]207
[354]208         CASE ( 'shf*' )
[667]209             DO  i = nxlg, nxrg
210                DO  j = nysg, nyng
[354]211                   shf_av(j,i) = shf_av(j,i) / REAL( average_count_3d )
212                ENDDO
213             ENDDO
[367]214
[1]215          CASE ( 't*' )
[667]216             DO  i = nxlg, nxrg
217                DO  j = nysg, nyng
[1]218                   ts_av(j,i) = ts_av(j,i) / REAL( average_count_3d )
219                ENDDO
220             ENDDO
221
222          CASE ( 'u' )
[667]223             DO  i = nxlg, nxrg
224                DO  j = nysg, nyng
[1]225                   DO  k = nzb, nzt+1
226                      u_av(k,j,i) = u_av(k,j,i) / REAL( average_count_3d )
227                   ENDDO
228                ENDDO
229             ENDDO
230
231          CASE ( 'u*' )
[667]232             DO  i = nxlg, nxrg
233                DO  j = nysg, nyng
[1]234                   us_av(j,i) = us_av(j,i) / REAL( average_count_3d )
235                ENDDO
236             ENDDO
237
238          CASE ( 'v' )
[667]239             DO  i = nxlg, nxrg
240                DO  j = nysg, nyng
[1]241                   DO  k = nzb, nzt+1
242                      v_av(k,j,i) = v_av(k,j,i) / REAL( average_count_3d )
243                   ENDDO
244                ENDDO
245             ENDDO
246
247          CASE ( 'vpt' )
[667]248             DO  i = nxlg, nxrg
249                DO  j = nysg, nyng
[1]250                   DO  k = nzb, nzt+1
251                      vpt_av(k,j,i) = vpt_av(k,j,i) / REAL( average_count_3d )
252                   ENDDO
253                ENDDO
254             ENDDO
255
256          CASE ( 'w' )
[667]257             DO  i = nxlg, nxrg
258                DO  j = nysg, nyng
[1]259                   DO  k = nzb, nzt+1
260                      w_av(k,j,i) = w_av(k,j,i) / REAL( average_count_3d )
261                   ENDDO
262                ENDDO
263             ENDDO
264
[72]265          CASE ( 'z0*' )
[667]266             DO  i = nxlg, nxrg
267                DO  j = nysg, nyng
[72]268                   z0_av(j,i) = z0_av(j,i) / REAL( average_count_3d )
269                ENDDO
270             ENDDO
271
[1]272          CASE DEFAULT
273!
274!--          User-defined quantity
275             CALL user_3d_data_averaging( 'average', doav(ii) )
276
277       END SELECT
278
279    ENDDO
280
281!
282!-- Reset the counter
283    average_count_3d = 0.0
284
285    CALL cpu_log (log_point(35),'average_3d_data','stop','nobarrier')
286
287
288 END SUBROUTINE average_3d_data
Note: See TracBrowser for help on using the repository browser.