source: palm/trunk/SOURCE/init_3d_model.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: 53.5 KB
Line 
1#if defined( __ibmy_special )
2@PROCESS NOOPTimize
3#endif
4 SUBROUTINE init_3d_model
5
6!------------------------------------------------------------------------------!
7! Current revisions:
8! -----------------
9! nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng in loops and
10! allocation of arrays. Calls of exchange_horiz are modified.
11! Call ws_init to initialize arrays needed for statistical evaluation and
12! optimization when ws-scheme is used.
13!
14!
15! Initial volume flow is now calculated by using the variable hom_sum.
16! Therefore the correction of initial volume flow for non-flat topography
17! removed (removed u_nzb_p1_for_vfc and v_nzb_p1_for_vfc)
18!
19! Changed surface boundary conditions for u and v in case of ibc_uv_b == 0 from
20! mirror bc to dirichlet boundary conditions (u=v=0), so that k=nzb is
21! representative for the height z0
22!
23! Bugfix: type conversion of '1' to 64bit for the MAX function (ngp_3d_inner)
24!
25! Former revisions:
26! -----------------
27! $Id: init_3d_model.f90 667 2010-12-23 12:06:00Z suehring $
28!
29! 622 2010-12-10 08:08:13Z raasch
30! optional barriers included in order to speed up collective operations
31!
32! 560 2010-09-09 10:06:09Z weinreis
33! bugfix: correction of calculating ngp_3d for 64 bit
34!
35! 485 2010-02-05 10:57:51Z raasch
36! calculation of ngp_3d + ngp_3d_inner changed because they have now 64 bit
37!
38! 407 2009-12-01 15:01:15Z maronga
39! var_ts is replaced by dots_max
40! Enabled passive scalar/humidity wall fluxes for non-flat topography
41!
42! 388 2009-09-23 09:40:33Z raasch
43! Initialization of prho added.
44! bugfix: correction of initial volume flow for non-flat topography
45! bugfix: zero initialization of arrays within buildings for 'cyclic_fill'
46! bugfix: avoid that ngp_2dh_s_inner becomes zero
47! initializing_actions='read_data_for_recycling' renamed to 'cyclic_fill', now
48! independent of turbulent_inflow
49! Output of messages replaced by message handling routine.
50! Set the starting level and the vertical smoothing factor used for
51! the external pressure gradient
52! +conserve_volume_flow_mode: 'default', 'initial_profiles', 'inflow_profile'
53! and 'bulk_velocity'
54! If the inversion height calculated by the prerun is zero,
55! inflow_damping_height must be explicitly specified.
56!
57! 181 2008-07-30 07:07:47Z raasch
58! bugfix: zero assignments to tendency arrays in case of restarts,
59! further extensions and modifications in the initialisation of the plant
60! canopy model,
61! allocation of hom_sum moved to parin, initialization of spectrum_x|y directly
62! after allocating theses arrays,
63! read data for recycling added as new initialization option,
64! dummy allocation for diss
65!
66! 138 2007-11-28 10:03:58Z letzel
67! New counter ngp_2dh_s_inner.
68! Allow new case bc_uv_t = 'dirichlet_0' for channel flow.
69! Corrected calculation of initial volume flow for 'set_1d-model_profiles' and
70! 'set_constant_profiles' in case of buildings in the reference cross-sections.
71!
72! 108 2007-08-24 15:10:38Z letzel
73! Flux initialization in case of coupled runs, +momentum fluxes at top boundary,
74! +arrays for phase speed c_u, c_v, c_w, indices for u|v|w_m_l|r changed
75! +qswst_remote in case of atmosphere model with humidity coupled to ocean
76! Rayleigh damping for ocean, optionally calculate km and kh from initial
77! TKE e_init
78!
79! 97 2007-06-21 08:23:15Z raasch
80! Initialization of salinity, call of init_ocean
81!
82! 87 2007-05-22 15:46:47Z raasch
83! var_hom and var_sum renamed pr_palm
84!
85! 75 2007-03-22 09:54:05Z raasch
86! Arrays for radiation boundary conditions are allocated (u_m_l, u_m_r, etc.),
87! bugfix for cases with the outflow damping layer extending over more than one
88! subdomain, moisture renamed humidity,
89! new initializing action "by_user" calls user_init_3d_model,
90! precipitation_amount/rate, ts_value are allocated, +module netcdf_control,
91! initial velocities at nzb+1 are regarded for volume
92! flow control in case they have been set zero before (to avoid small timesteps)
93! -uvmean_outflow, uxrp, vynp eliminated
94!
95! 19 2007-02-23 04:53:48Z raasch
96! +handling of top fluxes
97!
98! RCS Log replace by Id keyword, revision history cleaned up
99!
100! Revision 1.49  2006/08/22 15:59:07  raasch
101! No optimization of this file on the ibmy (Yonsei Univ.)
102!
103! Revision 1.1  1998/03/09 16:22:22  raasch
104! Initial revision
105!
106!
107! Description:
108! ------------
109! Allocation of arrays and initialization of the 3D model via
110! a) pre-run the 1D model
111! or
112! b) pre-set constant linear profiles
113! or
114! c) read values of a previous run
115!------------------------------------------------------------------------------!
116
117    USE advec_ws
118    USE arrays_3d
119    USE averaging
120    USE cloud_parameters
121    USE constants
122    USE control_parameters
123    USE cpulog
124    USE indices
125    USE interfaces
126    USE model_1d
127    USE netcdf_control
128    USE particle_attributes
129    USE pegrid
130    USE profil_parameter
131    USE random_function_mod
132    USE statistics
133
134    IMPLICIT NONE
135
136    INTEGER ::  i, ind_array(1), j, k, sr
137
138    INTEGER, DIMENSION(:), ALLOCATABLE ::  ngp_2dh_l
139
140    INTEGER, DIMENSION(:,:), ALLOCATABLE ::  ngp_2dh_outer_l,  &
141         ngp_2dh_s_inner_l
142
143    REAL ::  a, b
144
145    REAL, DIMENSION(1:2) ::  volume_flow_area_l, volume_flow_initial_l
146
147    REAL, DIMENSION(:), ALLOCATABLE ::  ngp_3d_inner_l, ngp_3d_inner_tmp
148
149
150!
151!-- Allocate arrays
152    ALLOCATE( ngp_2dh(0:statistic_regions), ngp_2dh_l(0:statistic_regions), &
153              ngp_3d(0:statistic_regions),                                  &
154              ngp_3d_inner(0:statistic_regions),                            &
155              ngp_3d_inner_l(0:statistic_regions),                          &
156              ngp_3d_inner_tmp(0:statistic_regions),                        &
157              sums_divnew_l(0:statistic_regions),                           &
158              sums_divold_l(0:statistic_regions) )
159    ALLOCATE( dp_smooth_factor(nzb:nzt), rdf(nzb+1:nzt) )
160    ALLOCATE( ngp_2dh_outer(nzb:nzt+1,0:statistic_regions),                 &
161              ngp_2dh_outer_l(nzb:nzt+1,0:statistic_regions),               &
162              ngp_2dh_s_inner(nzb:nzt+1,0:statistic_regions),               &
163              ngp_2dh_s_inner_l(nzb:nzt+1,0:statistic_regions),             &
164              rmask(nysg:nyng,nxlg:nxrg,0:statistic_regions),           &
165              sums(nzb:nzt+1,pr_palm+max_pr_user),                          &
166              sums_l(nzb:nzt+1,pr_palm+max_pr_user,0:threads_per_task-1),   &
167              sums_l_l(nzb:nzt+1,0:statistic_regions,0:threads_per_task-1), &
168              sums_up_fraction_l(10,3,0:statistic_regions),                 &
169              sums_wsts_bc_l(nzb:nzt+1,0:statistic_regions),                &
170              ts_value(dots_max,0:statistic_regions) )
171    ALLOCATE( km_damp_x(nxlg:nxrg), km_damp_y(nysg:nyng) )
172
173    ALLOCATE( rif_1(nysg:nyng,nxlg:nxrg), shf_1(nysg:nyng,nxlg:nxrg), &
174              ts(nysg:nyng,nxlg:nxrg), tswst_1(nysg:nyng,nxlg:nxrg),  &
175              us(nysg:nyng,nxlg:nxrg), usws_1(nysg:nyng,nxlg:nxrg),   &
176              uswst_1(nysg:nyng,nxlg:nxrg),                               &
177              vsws_1(nysg:nyng,nxlg:nxrg),                                &
178              vswst_1(nysg:nyng,nxlg:nxrg), z0(nysg:nyng,nxlg:nxrg) )
179
180    IF ( timestep_scheme(1:5) /= 'runge' )  THEN
181!
182!--    Leapfrog scheme needs two timelevels of diffusion quantities
183       ALLOCATE( rif_2(nysg:nyng,nxlg:nxrg),   &
184                 shf_2(nysg:nyng,nxlg:nxrg),   &
185                 tswst_2(nysg:nyng,nxlg:nxrg), &
186                 usws_2(nysg:nyng,nxlg:nxrg),  &
187                 uswst_2(nysg:nyng,nxlg:nxrg), &
188                 vswst_2(nysg:nyng,nxlg:nxrg), &
189                 vsws_2(nysg:nyng,nxlg:nxrg) )
190    ENDIF
191
192    ALLOCATE( d(nzb+1:nzta,nys:nyna,nxl:nxra),         &
193              e_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg),  &
194              e_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg),  &
195              e_3(nzb:nzt+1,nysg:nyng,nxlg:nxrg),  &
196              kh_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg), &
197              km_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg), &
198              p(nzb:nzt+1,nysg:nyng,nxlg:nxrg),    &
199              pt_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg), &
200              pt_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg), &
201              pt_3(nzb:nzt+1,nysg:nyng,nxlg:nxrg), &
202              tend(nzb:nzt+1,nysg:nyng,nxlg:nxrg), &
203              u_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg),  &
204              u_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg),  &
205              u_3(nzb:nzt+1,nysg:nyng,nxlg:nxrg),  &
206              v_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg), &
207              v_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg), &
208              v_3(nzb:nzt+1,nysg:nyng,nxlg:nxrg), &
209              w_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg),  &
210              w_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg),  &
211              w_3(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
212
213    IF ( timestep_scheme(1:5) /= 'runge' )  THEN
214       ALLOCATE( kh_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg), &
215                 km_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
216    ENDIF
217
218    IF ( humidity  .OR.  passive_scalar ) THEN
219!
220!--    2D-humidity/scalar arrays
221       ALLOCATE ( qs(nysg:nyng,nxlg:nxrg),     &
222                  qsws_1(nysg:nyng,nxlg:nxrg), &
223                  qswst_1(nysg:nyng,nxlg:nxrg) )
224
225       IF ( timestep_scheme(1:5) /= 'runge' )  THEN
226          ALLOCATE( qsws_2(nysg:nyng,nxlg:nxrg), &
227                    qswst_2(nysg:nyng,nxlg:nxrg) )
228       ENDIF
229!
230!--    3D-humidity/scalar arrays
231       ALLOCATE( q_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg), &
232                 q_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg), &
233                 q_3(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
234
235!
236!--    3D-arrays needed for humidity only
237       IF ( humidity )  THEN
238          ALLOCATE( vpt_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
239
240          IF ( timestep_scheme(1:5) /= 'runge' )  THEN
241             ALLOCATE( vpt_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
242          ENDIF
243
244          IF ( cloud_physics ) THEN
245!
246!--          Liquid water content
247             ALLOCATE ( ql_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
248!
249!--          Precipitation amount and rate (only needed if output is switched)
250             ALLOCATE( precipitation_amount(nysg:nyng,nxlg:nxrg), &
251                       precipitation_rate(nysg:nyng,nxlg:nxrg) )
252          ENDIF
253
254          IF ( cloud_droplets )  THEN
255!
256!--          Liquid water content, change in liquid water content,
257!--          real volume of particles (with weighting), volume of particles
258             ALLOCATE ( ql_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg), &
259                        ql_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg), &
260                        ql_v(nzb:nzt+1,nysg:nyng,nxlg:nxrg), &
261                        ql_vp(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
262          ENDIF
263
264       ENDIF
265
266    ENDIF
267
268    IF ( ocean )  THEN
269       ALLOCATE( saswsb_1(nysg:nyng,nxlg:nxrg), &
270                 saswst_1(nysg:nyng,nxlg:nxrg) )
271       ALLOCATE( prho_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg), &
272                 rho_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg),  &
273                 sa_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg),   &
274                 sa_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg),   &
275                 sa_3(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
276       prho => prho_1
277       rho  => rho_1  ! routines calc_mean_profile and diffusion_e require
278                      ! density to be apointer
279       IF ( humidity_remote )  THEN
280          ALLOCATE( qswst_remote(nysg:nyng,nxlg:nxrg))
281          qswst_remote = 0.0
282       ENDIF
283    ENDIF
284
285!
286!-- 3D-array for storing the dissipation, needed for calculating the sgs
287!-- particle velocities
288    IF ( use_sgs_for_particles )  THEN
289       ALLOCATE ( diss(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
290    ELSE
291       ALLOCATE ( diss(2,2,2) )  ! required because diss is used as a
292                                 ! formal parameter
293    ENDIF
294
295    IF ( dt_dosp /= 9999999.9 )  THEN
296       ALLOCATE( spectrum_x( 1:nx/2, 1:10, 1:10 ), &
297                 spectrum_y( 1:ny/2, 1:10, 1:10 ) )
298       spectrum_x = 0.0
299       spectrum_y = 0.0
300    ENDIF
301
302!
303!-- 3D-arrays for the leaf area density and the canopy drag coefficient
304    IF ( plant_canopy ) THEN
305       ALLOCATE ( lad_s(nzb:nzt+1,nysg:nyng,nxlg:nxrg),  &
306                  lad_u(nzb:nzt+1,nysg:nyng,nxlg:nxrg),  &
307                  lad_v(nzb:nzt+1,nysg:nyng,nxlg:nxrg),  &
308                  lad_w(nzb:nzt+1,nysg:nyng,nxlg:nxrg),  &
309                  cdc(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
310
311       IF ( passive_scalar ) THEN
312          ALLOCATE ( sls(nzb:nzt+1,nysg:nyng,nxlg:nxrg),   &
313                     sec(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ) 
314       ENDIF
315
316       IF ( cthf /= 0.0 ) THEN
317          ALLOCATE ( lai(nzb:nzt+1,nysg:nyng,nxlg:nxrg),   &
318                     canopy_heat_flux(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
319       ENDIF
320
321    ENDIF
322
323!
324!-- 4D-array for storing the Rif-values at vertical walls
325    IF ( topography /= 'flat' )  THEN
326       ALLOCATE( rif_wall(nzb:nzt+1,nysg:nyng,nxlg:nxrg,1:4) )
327       rif_wall = 0.0
328    ENDIF
329
330!
331!-- Arrays to store velocity data from t-dt and the phase speeds which
332!-- are needed for radiation boundary conditions
333    IF ( outflow_l )  THEN
334       ALLOCATE( u_m_l(nzb:nzt+1,nysg:nyng,1:2), &
335                 v_m_l(nzb:nzt+1,nysg:nyng,0:1), &
336                 w_m_l(nzb:nzt+1,nysg:nyng,0:1) )
337    ENDIF
338    IF ( outflow_r )  THEN
339       ALLOCATE( u_m_r(nzb:nzt+1,nysg:nyng,nx-1:nx), &
340                 v_m_r(nzb:nzt+1,nysg:nyng,nx-1:nx), &
341                 w_m_r(nzb:nzt+1,nysg:nyng,nx-1:nx) )
342    ENDIF
343    IF ( outflow_l  .OR.  outflow_r )  THEN
344       ALLOCATE( c_u(nzb:nzt+1,nysg:nyng), c_v(nzb:nzt+1,nysg:nyng), &
345                 c_w(nzb:nzt+1,nysg:nyng) )
346    ENDIF
347    IF ( outflow_s )  THEN
348       ALLOCATE( u_m_s(nzb:nzt+1,0:1,nxlg:nxrg), &
349                 v_m_s(nzb:nzt+1,1:2,nxlg:nxrg), &
350                 w_m_s(nzb:nzt+1,0:1,nxlg:nxrg) )
351    ENDIF
352    IF ( outflow_n )  THEN
353       ALLOCATE( u_m_n(nzb:nzt+1,ny-1:ny,nxlg:nxrg), &
354                 v_m_n(nzb:nzt+1,ny-1:ny,nxlg:nxrg), &
355                 w_m_n(nzb:nzt+1,ny-1:ny,nxlg:nxrg) )
356    ENDIF
357    IF ( outflow_s  .OR.  outflow_n )  THEN
358       ALLOCATE( c_u(nzb:nzt+1,nxlg:nxrg), c_v(nzb:nzt+1,nxlg:nxrg), &
359                 c_w(nzb:nzt+1,nxlg:nxrg) )
360    ENDIF
361
362!
363!-- Initial assignment of the pointers
364    IF ( timestep_scheme(1:5) /= 'runge' )  THEN
365
366       rif_m   => rif_1;    rif   => rif_2
367       shf_m   => shf_1;    shf   => shf_2
368       tswst_m => tswst_1;  tswst => tswst_2
369       usws_m  => usws_1;   usws  => usws_2
370       uswst_m => uswst_1;  uswst => uswst_2
371       vsws_m  => vsws_1;   vsws  => vsws_2
372       vswst_m => vswst_1;  vswst => vswst_2
373       e_m  => e_1;   e  => e_2;   e_p  => e_3;   te_m  => e_3
374       kh_m => kh_1;  kh => kh_2
375       km_m => km_1;  km => km_2
376       pt_m => pt_1;  pt => pt_2;  pt_p => pt_3;  tpt_m => pt_3
377       u_m  => u_1;   u  => u_2;   u_p  => u_3;   tu_m  => u_3
378       v_m  => v_1;   v  => v_2;   v_p  => v_3;   tv_m  => v_3
379       w_m  => w_1;   w  => w_2;   w_p  => w_3;   tw_m  => w_3
380
381       IF ( humidity  .OR.  passive_scalar )  THEN
382          qsws_m  => qsws_1;   qsws  => qsws_2
383          qswst_m => qswst_1;  qswst => qswst_2
384          q_m    => q_1;     q    => q_2;     q_p => q_3;     tq_m => q_3
385          IF ( humidity )        vpt_m  => vpt_1;   vpt  => vpt_2
386          IF ( cloud_physics )   ql   => ql_1
387          IF ( cloud_droplets )  THEN
388             ql   => ql_1
389             ql_c => ql_2
390          ENDIF
391       ENDIF
392
393    ELSE
394
395       rif   => rif_1
396       shf   => shf_1
397       tswst => tswst_1
398       usws  => usws_1
399       uswst => uswst_1
400       vsws  => vsws_1
401       vswst => vswst_1
402       e     => e_1;   e_p  => e_2;   te_m  => e_3;   e_m  => e_3
403       kh    => kh_1
404       km    => km_1
405       pt    => pt_1;  pt_p => pt_2;  tpt_m => pt_3;  pt_m => pt_3
406       u     => u_1;   u_p  => u_2;   tu_m  => u_3;   u_m  => u_3
407       v     => v_1;   v_p  => v_2;   tv_m  => v_3;   v_m  => v_3
408       w     => w_1;   w_p  => w_2;   tw_m  => w_3;   w_m  => w_3
409
410       IF ( humidity  .OR.  passive_scalar )  THEN
411          qsws   => qsws_1
412          qswst  => qswst_1
413          q      => q_1;     q_p  => q_2;     tq_m  => q_3;    q_m => q_3
414          IF ( humidity )        vpt  => vpt_1
415          IF ( cloud_physics )   ql   => ql_1
416          IF ( cloud_droplets )  THEN
417             ql   => ql_1
418             ql_c => ql_2
419          ENDIF
420       ENDIF
421
422       IF ( ocean )  THEN
423          saswsb => saswsb_1
424          saswst => saswst_1
425          sa     => sa_1;    sa_p => sa_2;    tsa_m => sa_3
426       ENDIF
427
428    ENDIF
429
430!
431!-- Initialize model variables
432    IF ( TRIM( initializing_actions ) /= 'read_restart_data'  .AND.  &
433         TRIM( initializing_actions ) /= 'cyclic_fill' )  THEN
434!
435!--    First model run of a possible job queue.
436!--    Initial profiles of the variables must be computes.
437       IF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
438!
439!--       Use solutions of the 1D model as initial profiles,
440!--       start 1D model
441          CALL init_1d_model
442!
443!--       Transfer initial profiles to the arrays of the 3D model
444          DO  i = nxlg, nxrg
445             DO  j = nysg, nyng
446                e(:,j,i)  = e1d
447                kh(:,j,i) = kh1d
448                km(:,j,i) = km1d
449                pt(:,j,i) = pt_init
450                u(:,j,i)  = u1d
451                v(:,j,i)  = v1d
452             ENDDO
453          ENDDO
454
455          IF ( humidity  .OR.  passive_scalar )  THEN
456             DO  i = nxlg, nxrg
457                DO  j = nysg, nyng
458                   q(:,j,i) = q_init
459                ENDDO
460             ENDDO
461          ENDIF
462
463          IF ( .NOT. constant_diffusion )  THEN
464             DO  i = nxlg, nxrg
465                DO  j = nysg, nyng
466                   e(:,j,i)  = e1d
467                ENDDO
468             ENDDO
469!
470!--          Store initial profiles for output purposes etc.
471             hom(:,1,25,:) = SPREAD( l1d, 2, statistic_regions+1 )
472
473             IF ( prandtl_layer )  THEN
474                rif  = rif1d(nzb+1)
475                ts   = 0.0  ! could actually be computed more accurately in the
476                            ! 1D model. Update when opportunity arises.
477                us   = us1d
478                usws = usws1d
479                vsws = vsws1d
480             ELSE
481                ts   = 0.0  ! must be set, because used in
482                rif  = 0.0  ! flowste
483                us   = 0.0
484                usws = 0.0
485                vsws = 0.0
486             ENDIF
487
488          ELSE
489             e    = 0.0  ! must be set, because used in
490             rif  = 0.0  ! flowste
491             ts   = 0.0
492             us   = 0.0
493             usws = 0.0
494             vsws = 0.0
495          ENDIF
496          uswst = top_momentumflux_u
497          vswst = top_momentumflux_v
498
499!
500!--       In every case qs = 0.0 (see also pt)
501!--       This could actually be computed more accurately in the 1D model.
502!--       Update when opportunity arises!
503          IF ( humidity  .OR.  passive_scalar )  qs = 0.0
504
505!
506!--       inside buildings set velocities back to zero
507          IF ( topography /= 'flat' )  THEN
508             DO  i = nxl-1, nxr+1
509                DO  j = nys-1, nyn+1
510                   u(nzb:nzb_u_inner(j,i),j,i) = 0.0
511                   v(nzb:nzb_v_inner(j,i),j,i) = 0.0
512                ENDDO
513             ENDDO
514             
515!
516!--          WARNING: The extra boundary conditions set after running the
517!--          -------  1D model impose an error on the divergence one layer
518!--                   below the topography; need to correct later
519!--          ATTENTION: Provisional correction for Piacsek & Williams
520!--          ---------  advection scheme: keep u and v zero one layer below
521!--                     the topography.
522!
523!--           Following was removed, because mirror boundary condition are
524!--           replaced by dirichlet boundary conditions
525!
526!             IF ( ibc_uv_b == 0 )  THEN
527!!
528!!--             Satisfying the Dirichlet condition with an extra layer below
529!!--             the surface where the u and v component change their sign.
530!                DO  i = nxl-1, nxr+1
531!                   DO  j = nys-1, nyn+1
532!                      IF ( nzb_u_inner(j,i) == 0 ) u(0,j,i) = -u(1,j,i)
533!                      IF ( nzb_v_inner(j,i) == 0 ) v(0,j,i) = -v(1,j,i)
534!                   ENDDO
535!                ENDDO
536!
537!             ELSE
538             IF ( ibc_uv_b == 1 )  THEN
539!
540!--             Neumann condition
541                DO  i = nxl-1, nxr+1
542                   DO  j = nys-1, nyn+1
543                      IF ( nzb_u_inner(j,i) == 0 ) u(0,j,i) = u(1,j,i)
544                      IF ( nzb_v_inner(j,i) == 0 ) v(0,j,i) = v(1,j,i)
545                   ENDDO
546                ENDDO
547
548             ENDIF
549
550          ENDIF
551
552       ELSEIF ( INDEX(initializing_actions, 'set_constant_profiles') /= 0 ) &
553       THEN
554!
555!--       Use constructed initial profiles (velocity constant with height,
556!--       temperature profile with constant gradient)
557          DO  i = nxlg, nxrg
558             DO  j = nysg, nyng
559                pt(:,j,i) = pt_init
560                u(:,j,i)  = u_init
561                v(:,j,i)  = v_init
562             ENDDO
563          ENDDO
564
565!
566!--       Set initial horizontal velocities at the lowest computational grid
567!--       levels to zero in order to avoid too small time steps caused by the
568!--       diffusion limit in the initial phase of a run (at k=1, dz/2 occurs
569!--       in the limiting formula!). The original values are stored to be later
570!--       used for volume flow control.
571          DO  i = nxlg, nxrg
572             DO  j = nysg, nyng
573                u(nzb:nzb_u_inner(j,i)+1,j,i) = 0.0
574                v(nzb:nzb_v_inner(j,i)+1,j,i) = 0.0
575             ENDDO
576          ENDDO
577
578          IF ( humidity  .OR.  passive_scalar )  THEN
579             DO  i = nxlg, nxrg
580                DO  j = nysg, nyng
581                   q(:,j,i) = q_init
582                ENDDO
583             ENDDO
584          ENDIF
585
586          IF ( ocean )  THEN
587             DO  i = nxlg, nxrg
588                DO  j = nysg, nyng
589                   sa(:,j,i) = sa_init
590                ENDDO
591             ENDDO
592          ENDIF
593         
594          IF ( constant_diffusion )  THEN
595             km   = km_constant
596             kh   = km / prandtl_number
597             e    = 0.0
598          ELSEIF ( e_init > 0.0 )  THEN
599             DO  k = nzb+1, nzt
600                km(k,:,:) = 0.1 * l_grid(k) * SQRT( e_init )
601             ENDDO
602             km(nzb,:,:)   = km(nzb+1,:,:)
603             km(nzt+1,:,:) = km(nzt,:,:)
604             kh   = km / prandtl_number
605             e    = e_init
606          ELSE
607             IF ( .NOT. ocean )  THEN
608                kh   = 0.01   ! there must exist an initial diffusion, because
609                km   = 0.01   ! otherwise no TKE would be produced by the
610                              ! production terms, as long as not yet
611                              ! e = (u*/cm)**2 at k=nzb+1
612             ELSE
613                kh   = 0.00001
614                km   = 0.00001
615             ENDIF
616             e    = 0.0
617          ENDIF
618          rif   = 0.0
619          ts    = 0.0
620          us    = 0.0
621          usws  = 0.0
622          uswst = top_momentumflux_u
623          vsws  = 0.0
624          vswst = top_momentumflux_v
625          IF ( humidity  .OR.  passive_scalar ) qs = 0.0
626
627!
628!--       Compute initial temperature field and other constants used in case
629!--       of a sloping surface
630          IF ( sloping_surface )  CALL init_slope
631
632       ELSEIF ( INDEX(initializing_actions, 'by_user') /= 0 ) &
633       THEN
634!
635!--       Initialization will completely be done by the user
636          CALL user_init_3d_model
637
638       ENDIF
639!
640!--    Bottom boundary
641       IF ( ibc_uv_b == 0 .OR. ibc_uv_b == 2  )  THEN
642          u(nzb,:,:) = 0.0
643          v(nzb,:,:) = 0.0
644       ENDIF
645
646!
647!--    Apply channel flow boundary condition
648       IF ( TRIM( bc_uv_t ) == 'dirichlet_0' )  THEN
649
650          u(nzt+1,:,:) = 0.0
651          v(nzt+1,:,:) = 0.0
652
653!--       For the Dirichlet condition to be correctly applied at the top, set
654!--       ug and vg to zero there
655          ug(nzt+1)    = 0.0
656          vg(nzt+1)    = 0.0
657
658       ENDIF
659
660!
661!--    Calculate virtual potential temperature
662       IF ( humidity ) vpt = pt * ( 1.0 + 0.61 * q )
663
664!
665!--    Store initial profiles for output purposes etc.
666       hom(:,1,5,:) = SPREAD( u(:,nys,nxl), 2, statistic_regions+1 )
667       hom(:,1,6,:) = SPREAD( v(:,nys,nxl), 2, statistic_regions+1 )
668       IF ( ibc_uv_b == 0 .OR. ibc_uv_b == 2)  THEN
669          hom(nzb,1,5,:) = 0.0   
670          hom(nzb,1,6,:) = 0.0 
671       ENDIF
672       hom(:,1,7,:)  = SPREAD( pt(:,nys,nxl), 2, statistic_regions+1 )
673       hom(:,1,23,:) = SPREAD( km(:,nys,nxl), 2, statistic_regions+1 )
674       hom(:,1,24,:) = SPREAD( kh(:,nys,nxl), 2, statistic_regions+1 )
675
676       IF ( ocean )  THEN
677!
678!--       Store initial salinity profile
679          hom(:,1,26,:)  = SPREAD( sa(:,nys,nxl), 2, statistic_regions+1 )
680       ENDIF
681
682       IF ( humidity )  THEN
683!
684!--       Store initial profile of total water content, virtual potential
685!--       temperature
686          hom(:,1,26,:) = SPREAD(   q(:,nys,nxl), 2, statistic_regions+1 )
687          hom(:,1,29,:) = SPREAD( vpt(:,nys,nxl), 2, statistic_regions+1 )
688          IF ( cloud_physics  .OR.  cloud_droplets ) THEN
689!
690!--          Store initial profile of specific humidity and potential
691!--          temperature
692             hom(:,1,27,:) = SPREAD(  q(:,nys,nxl), 2, statistic_regions+1 )
693             hom(:,1,28,:) = SPREAD( pt(:,nys,nxl), 2, statistic_regions+1 )
694          ENDIF
695       ENDIF
696
697       IF ( passive_scalar )  THEN
698!
699!--       Store initial scalar profile
700          hom(:,1,26,:) = SPREAD(  q(:,nys,nxl), 2, statistic_regions+1 )
701       ENDIF
702
703!
704!--    Initialize fluxes at bottom surface
705       IF ( use_surface_fluxes )  THEN
706
707          IF ( constant_heatflux )  THEN
708!
709!--          Heat flux is prescribed
710             IF ( random_heatflux )  THEN
711                CALL disturb_heatflux
712             ELSE
713                shf = surface_heatflux
714!
715!--             Over topography surface_heatflux is replaced by wall_heatflux(0)
716                IF ( TRIM( topography ) /= 'flat' )  THEN
717                   DO  i = nxlg, nxrg
718                      DO  j = nysg, nyng
719                         IF ( nzb_s_inner(j,i) /= 0 )  THEN
720                            shf(j,i) = wall_heatflux(0)
721                         ENDIF
722                      ENDDO
723                   ENDDO
724                ENDIF
725             ENDIF
726             IF ( ASSOCIATED( shf_m ) )  shf_m = shf
727          ENDIF
728
729!
730!--       Determine the near-surface water flux
731          IF ( humidity  .OR.  passive_scalar )  THEN
732             IF ( constant_waterflux )  THEN
733                qsws   = surface_waterflux
734!
735!--             Over topography surface_waterflux is replaced by
736!--             wall_humidityflux(0)
737                IF ( TRIM( topography ) /= 'flat' )  THEN
738                   wall_qflux = wall_humidityflux
739                   DO  i = nxlg, nxrg
740                      DO  j = nysg, nyng
741                         IF ( nzb_s_inner(j,i) /= 0 )  THEN
742                            qsws(j,i) = wall_qflux(0)
743                         ENDIF
744                      ENDDO
745                   ENDDO
746                ENDIF
747                IF ( ASSOCIATED( qsws_m ) )  qsws_m = qsws
748             ENDIF
749          ENDIF
750
751       ENDIF
752
753!
754!--    Initialize fluxes at top surface
755!--    Currently, only the heatflux and salinity flux can be prescribed.
756!--    The latent flux is zero in this case!
757       IF ( use_top_fluxes )  THEN
758
759          IF ( constant_top_heatflux )  THEN
760!
761!--          Heat flux is prescribed
762             tswst = top_heatflux
763             IF ( ASSOCIATED( tswst_m ) )  tswst_m = tswst
764
765             IF ( humidity  .OR.  passive_scalar )  THEN
766                qswst = 0.0
767                IF ( ASSOCIATED( qswst_m ) )  qswst_m = qswst
768             ENDIF
769
770             IF ( ocean )  THEN
771                saswsb = bottom_salinityflux
772                saswst = top_salinityflux
773             ENDIF
774          ENDIF
775
776!
777!--       Initialization in case of a coupled model run
778          IF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
779             tswst = 0.0
780             IF ( ASSOCIATED( tswst_m ) )  tswst_m = tswst
781          ENDIF
782
783       ENDIF
784
785!
786!--    Initialize Prandtl layer quantities
787       IF ( prandtl_layer )  THEN
788
789          z0 = roughness_length
790
791          IF ( .NOT. constant_heatflux )  THEN 
792!
793!--          Surface temperature is prescribed. Here the heat flux cannot be
794!--          simply estimated, because therefore rif, u* and theta* would have
795!--          to be computed by iteration. This is why the heat flux is assumed
796!--          to be zero before the first time step. It approaches its correct
797!--          value in the course of the first few time steps.
798             shf   = 0.0
799             IF ( ASSOCIATED( shf_m ) )  shf_m = 0.0
800          ENDIF
801
802          IF ( humidity  .OR.  passive_scalar )  THEN
803             IF ( .NOT. constant_waterflux )  THEN
804                qsws   = 0.0
805                IF ( ASSOCIATED( qsws_m ) )   qsws_m = 0.0
806             ENDIF
807          ENDIF
808
809       ENDIF
810
811
812!
813!--    For the moment, perturbation pressure and vertical velocity are zero
814       p = 0.0; w = 0.0
815
816!
817!--    Initialize array sums (must be defined in first call of pres)
818       sums = 0.0
819
820!
821!--    Treating cloud physics, liquid water content and precipitation amount
822!--    are zero at beginning of the simulation
823       IF ( cloud_physics )  THEN
824          ql = 0.0
825          IF ( precipitation )  precipitation_amount = 0.0
826       ENDIF
827
828!
829!--    Impose vortex with vertical axis on the initial velocity profile
830       IF ( INDEX( initializing_actions, 'initialize_vortex' ) /= 0 )  THEN
831          CALL init_rankine
832       ENDIF
833
834!
835!--    Impose temperature anomaly (advection test only)
836       IF ( INDEX( initializing_actions, 'initialize_ptanom' ) /= 0 )  THEN
837          CALL init_pt_anomaly
838       ENDIF
839
840!
841!--    If required, change the surface temperature at the start of the 3D run
842       IF ( pt_surface_initial_change /= 0.0 )  THEN
843          pt(nzb,:,:) = pt(nzb,:,:) + pt_surface_initial_change
844       ENDIF
845
846!
847!--    If required, change the surface humidity/scalar at the start of the 3D
848!--    run
849       IF ( ( humidity .OR. passive_scalar ) .AND. &
850            q_surface_initial_change /= 0.0 )  THEN
851          q(nzb,:,:) = q(nzb,:,:) + q_surface_initial_change
852       ENDIF
853
854!
855!--    Initialize the random number generator (from numerical recipes)
856       CALL random_function_ini
857
858!
859!--    Impose random perturbation on the horizontal velocity field and then
860!--    remove the divergences from the velocity field
861       IF ( create_disturbances )  THEN
862          CALL disturb_field( nzb_u_inner, tend, u )
863          CALL disturb_field( nzb_v_inner, tend, v )
864          n_sor = nsor_ini
865          CALL pres
866          n_sor = nsor
867       ENDIF
868
869!
870!--    Once again set the perturbation pressure explicitly to zero in order to
871!--    assure that it does not generate any divergences in the first time step.
872!--    At t=0 the velocity field is free of divergence (as constructed above).
873!--    Divergences being created during a time step are not yet known and thus
874!--    cannot be corrected during the time step yet.
875       p = 0.0
876
877!
878!--    Initialize old and new time levels.
879       IF ( timestep_scheme(1:5) /= 'runge' )  THEN
880          e_m = e; pt_m = pt; u_m = u; v_m = v; w_m = w; kh_m = kh; km_m = km
881       ELSE
882          te_m = 0.0; tpt_m = 0.0; tu_m = 0.0; tv_m = 0.0; tw_m = 0.0
883       ENDIF
884       e_p = e; pt_p = pt; u_p = u; v_p = v; w_p = w
885
886       IF ( humidity  .OR.  passive_scalar )  THEN
887          IF ( ASSOCIATED( q_m ) )  q_m = q
888          IF ( timestep_scheme(1:5) == 'runge' )  tq_m = 0.0
889          q_p = q
890          IF ( humidity  .AND.  ASSOCIATED( vpt_m ) )  vpt_m = vpt
891       ENDIF
892
893       IF ( ocean )  THEN
894          tsa_m = 0.0
895          sa_p  = sa
896       ENDIF
897       
898
899    ELSEIF ( TRIM( initializing_actions ) == 'read_restart_data'  .OR.    &
900         TRIM( initializing_actions ) == 'cyclic_fill' )  &
901    THEN
902!
903!--    When reading data for cyclic fill of 3D prerun data, first read
904!--    some of the global variables from restart file
905       IF ( TRIM( initializing_actions ) == 'cyclic_fill' )  THEN
906
907          CALL read_parts_of_var_list
908          CALL close_file( 13 )
909
910!
911!--       Initialization of the turbulence recycling method
912          IF ( turbulent_inflow )  THEN
913!
914!--          Store temporally and horizontally averaged vertical profiles to be
915!--          used as mean inflow profiles
916             ALLOCATE( mean_inflow_profiles(nzb:nzt+1,5) )
917
918             mean_inflow_profiles(:,1) = hom_sum(:,1,0)    ! u
919             mean_inflow_profiles(:,2) = hom_sum(:,2,0)    ! v
920             mean_inflow_profiles(:,4) = hom_sum(:,4,0)    ! pt
921             mean_inflow_profiles(:,5) = hom_sum(:,8,0)    ! e
922
923!
924!--          Use these mean profiles for the inflow (provided that Dirichlet
925!--          conditions are used)
926             IF ( inflow_l )  THEN
927                DO  j = nysg, nyng
928                   DO  k = nzb, nzt+1
929                      u(k,j,nxlg:-1)  = mean_inflow_profiles(k,1)
930                      v(k,j,nxlg:-1)  = mean_inflow_profiles(k,2)
931                      w(k,j,nxlg:-1)  = 0.0
932                      pt(k,j,nxlg:-1) = mean_inflow_profiles(k,4)
933                      e(k,j,nxlg:-1)  = mean_inflow_profiles(k,5)
934                   ENDDO
935                ENDDO
936             ENDIF
937
938!
939!--          Calculate the damping factors to be used at the inflow. For a
940!--          turbulent inflow the turbulent fluctuations have to be limited
941!--          vertically because otherwise the turbulent inflow layer will grow
942!--          in time.
943             IF ( inflow_damping_height == 9999999.9 )  THEN
944!
945!--             Default: use the inversion height calculated by the prerun; if
946!--             this is zero, inflow_damping_height must be explicitly
947!--             specified.
948                IF ( hom_sum(nzb+6,pr_palm,0) /= 0.0 )  THEN
949                   inflow_damping_height = hom_sum(nzb+6,pr_palm,0)
950                ELSE
951                   WRITE( message_string, * ) 'inflow_damping_height must be ',&
952                        'explicitly specified because&the inversion height ', &
953                        'calculated by the prerun is zero.'
954                   CALL message( 'init_3d_model', 'PA0318', 1, 2, 0, 6, 0 )
955                ENDIF
956
957             ENDIF
958
959             IF ( inflow_damping_width == 9999999.9 )  THEN
960!
961!--             Default for the transition range: one tenth of the undamped
962!--             layer
963                inflow_damping_width = 0.1 * inflow_damping_height
964
965             ENDIF
966
967             ALLOCATE( inflow_damping_factor(nzb:nzt+1) )
968
969             DO  k = nzb, nzt+1
970
971                IF ( zu(k) <= inflow_damping_height )  THEN
972                   inflow_damping_factor(k) = 1.0
973                ELSEIF ( zu(k) <= inflow_damping_height +  &
974                                  inflow_damping_width )  THEN
975                   inflow_damping_factor(k) = 1.0 -                            &
976                                           ( zu(k) - inflow_damping_height ) / &
977                                           inflow_damping_width
978                ELSE
979                   inflow_damping_factor(k) = 0.0
980                ENDIF
981
982             ENDDO
983          ENDIF
984
985       ENDIF
986
987!
988!--    Read binary data from restart file
989
990       CALL read_3d_binary
991
992!
993!--    Inside buildings set velocities and TKE back to zero
994       IF ( TRIM( initializing_actions ) == 'cyclic_fill' .AND.  &
995            topography /= 'flat' )  THEN
996!
997!--       Inside buildings set velocities and TKE back to zero.
998!--       Other scalars (pt, q, s, km, kh, p, sa, ...) are ignored at present,
999!--       maybe revise later.
1000          IF ( timestep_scheme(1:5) == 'runge' )  THEN
1001             DO  i = nxlg, nxrg
1002                DO  j = nysg, nyng
1003                   u  (nzb:nzb_u_inner(j,i),j,i) = 0.0
1004                   v  (nzb:nzb_v_inner(j,i),j,i) = 0.0
1005                   w  (nzb:nzb_w_inner(j,i),j,i) = 0.0
1006                   e  (nzb:nzb_w_inner(j,i),j,i) = 0.0
1007                   u_m(nzb:nzb_u_inner(j,i),j,i) = 0.0
1008                   v_m(nzb:nzb_v_inner(j,i),j,i) = 0.0
1009                   w_m(nzb:nzb_w_inner(j,i),j,i) = 0.0
1010                   e_m(nzb:nzb_w_inner(j,i),j,i) = 0.0
1011                   tu_m(nzb:nzb_u_inner(j,i),j,i) = 0.0
1012                   tv_m(nzb:nzb_v_inner(j,i),j,i) = 0.0
1013                   tw_m(nzb:nzb_w_inner(j,i),j,i) = 0.0
1014                   te_m(nzb:nzb_w_inner(j,i),j,i) = 0.0
1015                   tpt_m(nzb:nzb_w_inner(j,i),j,i) = 0.0
1016                ENDDO
1017             ENDDO
1018          ELSE
1019             DO  i = nxlg, nxrg
1020                DO  j = nysg, nyng
1021                   u  (nzb:nzb_u_inner(j,i),j,i) = 0.0
1022                   v  (nzb:nzb_v_inner(j,i),j,i) = 0.0
1023                   w  (nzb:nzb_w_inner(j,i),j,i) = 0.0
1024                   e  (nzb:nzb_w_inner(j,i),j,i) = 0.0
1025                   u_m(nzb:nzb_u_inner(j,i),j,i) = 0.0
1026                   v_m(nzb:nzb_v_inner(j,i),j,i) = 0.0
1027                   w_m(nzb:nzb_w_inner(j,i),j,i) = 0.0
1028                   e_m(nzb:nzb_w_inner(j,i),j,i) = 0.0
1029                   u_p(nzb:nzb_u_inner(j,i),j,i) = 0.0
1030                   v_p(nzb:nzb_v_inner(j,i),j,i) = 0.0
1031                   w_p(nzb:nzb_w_inner(j,i),j,i) = 0.0
1032                   e_p(nzb:nzb_w_inner(j,i),j,i) = 0.0
1033                ENDDO
1034             ENDDO
1035          ENDIF
1036
1037       ENDIF
1038
1039!
1040!--    Calculate initial temperature field and other constants used in case
1041!--    of a sloping surface
1042       IF ( sloping_surface )  CALL init_slope
1043
1044!
1045!--    Initialize new time levels (only done in order to set boundary values
1046!--    including ghost points)
1047       e_p = e; pt_p = pt; u_p = u; v_p = v; w_p = w
1048       IF ( humidity  .OR.  passive_scalar )  q_p = q
1049       IF ( ocean )  sa_p = sa
1050
1051!
1052!--    Allthough tendency arrays are set in prognostic_equations, they have
1053!--    have to be predefined here because they are used (but multiplied with 0)
1054!--    there before they are set.
1055       IF ( timestep_scheme(1:5) == 'runge' )  THEN
1056          te_m = 0.0; tpt_m = 0.0; tu_m = 0.0; tv_m = 0.0; tw_m = 0.0
1057          IF ( humidity  .OR.  passive_scalar )  tq_m = 0.0
1058          IF ( ocean )  tsa_m = 0.0
1059       ENDIF
1060
1061    ELSE
1062!
1063!--    Actually this part of the programm should not be reached
1064       message_string = 'unknown initializing problem'
1065       CALL message( 'init_3d_model', 'PA0193', 1, 2, 0, 6, 0 )
1066    ENDIF
1067
1068
1069    IF (  TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
1070!
1071!--    Initialize old timelevels needed for radiation boundary conditions
1072       IF ( outflow_l )  THEN
1073          u_m_l(:,:,:) = u(:,:,1:2)
1074          v_m_l(:,:,:) = v(:,:,0:1)
1075          w_m_l(:,:,:) = w(:,:,0:1)
1076       ENDIF
1077       IF ( outflow_r )  THEN
1078          u_m_r(:,:,:) = u(:,:,nx-1:nx)
1079          v_m_r(:,:,:) = v(:,:,nx-1:nx)
1080          w_m_r(:,:,:) = w(:,:,nx-1:nx)
1081       ENDIF
1082       IF ( outflow_s )  THEN
1083          u_m_s(:,:,:) = u(:,0:1,:)
1084          v_m_s(:,:,:) = v(:,1:2,:)
1085          w_m_s(:,:,:) = w(:,0:1,:)
1086       ENDIF
1087       IF ( outflow_n )  THEN
1088          u_m_n(:,:,:) = u(:,ny-1:ny,:)
1089          v_m_n(:,:,:) = v(:,ny-1:ny,:)
1090          w_m_n(:,:,:) = w(:,ny-1:ny,:)
1091       ENDIF
1092       
1093    ENDIF
1094!
1095!-- Calculate the initial volume flow at the right and north boundary
1096    IF ( conserve_volume_flow ) THEN
1097
1098       volume_flow_initial_l = 0.0
1099       volume_flow_area_l    = 0.0
1100 
1101       IF  ( TRIM( initializing_actions ) == 'cyclic_fill' )  THEN
1102
1103          IF ( nxr == nx )  THEN
1104             DO  j = nys, nyn
1105                DO  k = nzb_2d(j,nx) + 1, nzt
1106                   volume_flow_initial_l(1) = volume_flow_initial_l(1) + &
1107                                              hom_sum(k,1,0) * dzw(k)
1108                   volume_flow_area_l(1)    = volume_flow_area_l(1) + dzw(k)
1109                ENDDO
1110             ENDDO
1111          ENDIF
1112         
1113          IF ( nyn == ny )  THEN
1114             DO  i = nxl, nxr
1115                DO  k = nzb_2d(ny,i) + 1, nzt 
1116                   volume_flow_initial_l(2) = volume_flow_initial_l(2) + &
1117                                               hom_sum(k,2,0) * dzw(k)
1118                   volume_flow_area_l(2)    = volume_flow_area_l(2) + dzw(k)
1119                ENDDO
1120             ENDDO
1121          ENDIF
1122
1123       ELSEIF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
1124
1125          IF ( nxr == nx )  THEN
1126             DO  j = nys, nyn
1127                DO  k = nzb_2d(j,nx) + 1, nzt
1128                   volume_flow_initial_l(1) = volume_flow_initial_l(1) + &
1129                                               u(k,j,nx) * dzw(k)
1130                   volume_flow_area_l(1)    = volume_flow_area_l(1) + dzw(k)
1131                ENDDO
1132             ENDDO
1133          ENDIF
1134         
1135          IF ( nyn == ny )  THEN
1136             DO  i = nxl, nxr
1137                DO  k = nzb_2d(ny,i) + 1, nzt 
1138                   volume_flow_initial_l(2) = volume_flow_initial_l(2) + &
1139                                              v(k,ny,i) * dzw(k)
1140                   volume_flow_area_l(2)    = volume_flow_area_l(2) + dzw(k)
1141                ENDDO
1142             ENDDO
1143          ENDIF
1144
1145       ENDIF
1146
1147#if defined( __parallel )
1148          CALL MPI_ALLREDUCE( volume_flow_initial_l(1), volume_flow_initial(1),&
1149                              2, MPI_REAL, MPI_SUM, comm2d, ierr )
1150          CALL MPI_ALLREDUCE( volume_flow_area_l(1), volume_flow_area(1),      &
1151                              2, MPI_REAL, MPI_SUM, comm2d, ierr )
1152
1153          CALL MPI_ALLREDUCE( volume_flow_initial_l(2), volume_flow_initial(2),&
1154                              2, MPI_REAL, MPI_SUM, comm2d, ierr )
1155          CALL MPI_ALLREDUCE( volume_flow_area_l(2), volume_flow_area(2),      &
1156                              2, MPI_REAL, MPI_SUM, comm2d, ierr )
1157
1158#else
1159          volume_flow_initial = volume_flow_initial_l
1160          volume_flow_area    = volume_flow_area_l
1161#endif 
1162
1163!
1164!--       In case of 'bulk_velocity' mode, volume_flow_initial is overridden
1165!--       and calculated from u|v_bulk instead.
1166          IF ( TRIM( conserve_volume_flow_mode ) == 'bulk_velocity' )  THEN
1167             volume_flow_initial(1) = u_bulk * volume_flow_area(1)
1168             volume_flow_initial(2) = v_bulk * volume_flow_area(2)
1169          ENDIF
1170
1171       ENDIF
1172!
1173!-- Initialization of the leaf area density
1174    IF ( plant_canopy ) THEN
1175 
1176       SELECT CASE ( TRIM( canopy_mode ) )
1177
1178          CASE( 'block' )
1179
1180             DO  i = nxlg, nxrg
1181                DO  j = nysg, nyng
1182                   lad_s(:,j,i) = lad(:)
1183                   cdc(:,j,i)   = drag_coefficient
1184                   IF ( passive_scalar ) THEN
1185                      sls(:,j,i) = leaf_surface_concentration
1186                      sec(:,j,i) = scalar_exchange_coefficient
1187                   ENDIF
1188                ENDDO
1189             ENDDO
1190
1191          CASE DEFAULT
1192
1193!
1194!--          The DEFAULT case is reached either if the parameter
1195!--          canopy mode contains a wrong character string or if the
1196!--          user has coded a special case in the user interface.
1197!--          There, the subroutine user_init_plant_canopy checks
1198!--          which of these two conditions applies.
1199             CALL user_init_plant_canopy
1200 
1201          END SELECT
1202
1203       CALL exchange_horiz( lad_s, nbgp )
1204       CALL exchange_horiz( cdc, nbgp )
1205
1206       IF ( passive_scalar ) THEN
1207          CALL exchange_horiz( sls, nbgp )
1208          CALL exchange_horiz( sec, nbgp )
1209       ENDIF
1210
1211!
1212!--    Sharp boundaries of the plant canopy in horizontal directions
1213!--    In vertical direction the interpolation is retained, as the leaf
1214!--    area density is initialised by prescribing a vertical profile
1215!--    consisting of piecewise linear segments. The upper boundary
1216!--    of the plant canopy is now defined by lad_w(pch_index,:,:) = 0.0.
1217
1218       DO  i = nxl, nxr
1219          DO  j = nys, nyn
1220             DO  k = nzb, nzt+1 
1221                IF ( lad_s(k,j,i) > 0.0 ) THEN
1222                   lad_u(k,j,i)   = lad_s(k,j,i) 
1223                   lad_u(k,j,i+1) = lad_s(k,j,i)
1224                   lad_v(k,j,i)   = lad_s(k,j,i)
1225                   lad_v(k,j+1,i) = lad_s(k,j,i)
1226                ENDIF
1227             ENDDO
1228             DO  k = nzb, nzt
1229                lad_w(k,j,i) = 0.5 * ( lad_s(k+1,j,i) + lad_s(k,j,i) )
1230             ENDDO
1231          ENDDO
1232       ENDDO
1233
1234       lad_w(pch_index,:,:) = 0.0
1235       lad_w(nzt+1,:,:)     = lad_w(nzt,:,:)
1236
1237       CALL exchange_horiz( lad_u, nbgp )
1238       CALL exchange_horiz( lad_v, nbgp )
1239       CALL exchange_horiz( lad_w, nbgp )
1240
1241!
1242!--    Initialisation of the canopy heat source distribution
1243       IF ( cthf /= 0.0 ) THEN
1244!
1245!--       Piecewise evaluation of the leaf area index by
1246!--       integration of the leaf area density
1247          lai(:,:,:) = 0.0
1248          DO  i = nxlg, nxrg
1249             DO  j = nysg, nyng
1250                DO  k = pch_index-1, 0, -1
1251                   lai(k,j,i) = lai(k+1,j,i) +                   &
1252                                ( 0.5 * ( lad_w(k+1,j,i) +       &
1253                                          lad_s(k+1,j,i) ) *     &
1254                                  ( zw(k+1) - zu(k+1) ) )  +     &
1255                                ( 0.5 * ( lad_w(k,j,i)   +       &
1256                                          lad_s(k+1,j,i) ) *     &
1257                                  ( zu(k+1) - zw(k) ) )
1258                ENDDO
1259             ENDDO
1260          ENDDO
1261
1262!
1263!--       Evaluation of the upward kinematic vertical heat flux within the
1264!--       canopy
1265          DO  i = nxlg, nxrg
1266             DO  j = nysg, nyng
1267                DO  k = 0, pch_index
1268                   canopy_heat_flux(k,j,i) = cthf *                    &
1269                                             exp( -0.6 * lai(k,j,i) )
1270                ENDDO
1271             ENDDO
1272          ENDDO
1273
1274!
1275!--       The near surface heat flux is derived from the heat flux
1276!--       distribution within the canopy
1277          shf(:,:) = canopy_heat_flux(0,:,:)
1278
1279          IF ( ASSOCIATED( shf_m ) ) shf_m = shf
1280
1281       ENDIF
1282
1283    ENDIF
1284
1285!
1286!-- If required, initialize dvrp-software
1287    IF ( dt_dvrp /= 9999999.9 )  CALL init_dvrp
1288
1289    IF ( ocean )  THEN
1290!
1291!--    Initialize quantities needed for the ocean model
1292       CALL init_ocean
1293
1294    ELSE
1295!
1296!--    Initialize quantities for handling cloud physics
1297!--    This routine must be called before init_particles, because
1298!--    otherwise, array pt_d_t, needed in data_output_dvrp (called by
1299!--    init_particles) is not defined.
1300       CALL init_cloud_physics
1301    ENDIF
1302
1303!
1304!-- If required, initialize particles
1305    IF ( particle_advection )  CALL init_particles
1306
1307!
1308!-- Initialize quantities for special advections schemes
1309    CALL init_advec
1310    IF ( momentum_advec == 'ws-scheme' .OR.  &
1311         scalar_advec == 'ws-scheme' ) CALL ws_init
1312
1313!
1314!-- Initialize Rayleigh damping factors
1315    rdf = 0.0
1316    IF ( rayleigh_damping_factor /= 0.0 )  THEN
1317       IF ( .NOT. ocean )  THEN
1318          DO  k = nzb+1, nzt
1319             IF ( zu(k) >= rayleigh_damping_height )  THEN
1320                rdf(k) = rayleigh_damping_factor * &
1321                      ( SIN( pi * 0.5 * ( zu(k) - rayleigh_damping_height )    &
1322                                      / ( zu(nzt) - rayleigh_damping_height ) )&
1323                      )**2
1324             ENDIF
1325          ENDDO
1326       ELSE
1327          DO  k = nzt, nzb+1, -1
1328             IF ( zu(k) <= rayleigh_damping_height )  THEN
1329                rdf(k) = rayleigh_damping_factor * &
1330                      ( SIN( pi * 0.5 * ( rayleigh_damping_height - zu(k) )    &
1331                                      / ( rayleigh_damping_height - zu(nzb+1)))&
1332                      )**2
1333             ENDIF
1334          ENDDO
1335       ENDIF
1336    ENDIF
1337
1338!
1339!-- Initialize the starting level and the vertical smoothing factor used for
1340!-- the external pressure gradient
1341    dp_smooth_factor = 1.0
1342    IF ( dp_external )  THEN
1343!
1344!--    Set the starting level dp_level_ind_b only if it has not been set before
1345!--    (e.g. in init_grid).
1346       IF ( dp_level_ind_b == 0 )  THEN
1347          ind_array = MINLOC( ABS( dp_level_b - zu ) )
1348          dp_level_ind_b = ind_array(1) - 1 + nzb 
1349                                        ! MINLOC uses lower array bound 1
1350       ENDIF
1351       IF ( dp_smooth )  THEN
1352          dp_smooth_factor(:dp_level_ind_b) = 0.0
1353          DO  k = dp_level_ind_b+1, nzt
1354             dp_smooth_factor(k) = 0.5 * ( 1.0 + SIN( pi * &
1355                  ( REAL( k - dp_level_ind_b ) /  &
1356                    REAL( nzt - dp_level_ind_b ) - 0.5 ) ) )
1357          ENDDO
1358       ENDIF
1359    ENDIF
1360
1361!
1362!-- Initialize diffusivities used within the outflow damping layer in case of
1363!-- non-cyclic lateral boundaries. A linear increase is assumed over the first
1364!-- half of the width of the damping layer
1365    IF ( bc_lr == 'dirichlet/radiation' )  THEN
1366
1367       DO  i = nxlg, nxrg
1368          IF ( i >= nx - outflow_damping_width )  THEN
1369             km_damp_x(i) = km_damp_max * MIN( 1.0,                    &
1370                            ( i - ( nx - outflow_damping_width ) ) /   &
1371                            REAL( outflow_damping_width/2 )            &
1372                                             )
1373          ELSE
1374             km_damp_x(i) = 0.0
1375          ENDIF
1376       ENDDO
1377
1378    ELSEIF ( bc_lr == 'radiation/dirichlet' )  THEN
1379
1380       DO  i = nxlg, nxrg
1381          IF ( i <= outflow_damping_width )  THEN
1382             km_damp_x(i) = km_damp_max * MIN( 1.0,                    &
1383                            ( outflow_damping_width - i ) /            &
1384                            REAL( outflow_damping_width/2 )            &
1385                                             )
1386          ELSE
1387             km_damp_x(i) = 0.0
1388          ENDIF
1389       ENDDO
1390
1391    ENDIF
1392
1393    IF ( bc_ns == 'dirichlet/radiation' )  THEN
1394
1395       DO  j = nysg, nyng
1396          IF ( j >= ny - outflow_damping_width )  THEN
1397             km_damp_y(j) = km_damp_max * MIN( 1.0,                    &
1398                            ( j - ( ny - outflow_damping_width ) ) /   &
1399                            REAL( outflow_damping_width/2 )            &
1400                                             )
1401          ELSE
1402             km_damp_y(j) = 0.0
1403          ENDIF
1404       ENDDO
1405
1406    ELSEIF ( bc_ns == 'radiation/dirichlet' )  THEN
1407
1408       DO  j = nysg, nyng
1409          IF ( j <= outflow_damping_width )  THEN
1410             km_damp_y(j) = km_damp_max * MIN( 1.0,                    &
1411                            ( outflow_damping_width - j ) /            &
1412                            REAL( outflow_damping_width/2 )            &
1413                                             )
1414          ELSE
1415             km_damp_y(j) = 0.0
1416          ENDIF
1417       ENDDO
1418
1419    ENDIF
1420
1421!
1422!-- Initialize local summation arrays for UP flow_statistics. This is necessary
1423!-- because they may not yet have been initialized when they are called from
1424!-- flow_statistics (or - depending on the chosen model run - are never
1425!-- initialized)
1426    sums_divnew_l      = 0.0
1427    sums_divold_l      = 0.0
1428    sums_l_l           = 0.0
1429    sums_up_fraction_l = 0.0
1430    sums_wsts_bc_l     = 0.0
1431
1432!
1433!-- Pre-set masks for regional statistics. Default is the total model domain.
1434    rmask = 1.0
1435
1436!
1437!-- User-defined initializing actions. Check afterwards, if maximum number
1438!-- of allowed timeseries is not exceeded
1439    CALL user_init
1440
1441    IF ( dots_num > dots_max )  THEN
1442       WRITE( message_string, * ) 'number of time series quantities exceeds', &
1443                                  ' its maximum of dots_max = ', dots_max,    &
1444                                  ' &Please increase dots_max in modules.f90.'
1445       CALL message( 'init_3d_model', 'PA0194', 1, 2, 0, 6, 0 )   
1446    ENDIF
1447
1448!
1449!-- Input binary data file is not needed anymore. This line must be placed
1450!-- after call of user_init!
1451    CALL close_file( 13 )
1452
1453!
1454!-- Compute total sum of active mask grid points
1455!-- ngp_2dh: number of grid points of a horizontal cross section through the
1456!--          total domain
1457!-- ngp_3d:  number of grid points of the total domain
1458    ngp_2dh_outer_l   = 0
1459    ngp_2dh_outer     = 0
1460    ngp_2dh_s_inner_l = 0
1461    ngp_2dh_s_inner   = 0
1462    ngp_2dh_l         = 0
1463    ngp_2dh           = 0
1464    ngp_3d_inner_l    = 0.0
1465    ngp_3d_inner      = 0
1466    ngp_3d            = 0
1467    ngp_sums          = ( nz + 2 ) * ( pr_palm + max_pr_user )
1468
1469    DO  sr = 0, statistic_regions
1470       DO  i = nxl, nxr
1471          DO  j = nys, nyn
1472             IF ( rmask(j,i,sr) == 1.0 )  THEN
1473!
1474!--             All xy-grid points
1475                ngp_2dh_l(sr) = ngp_2dh_l(sr) + 1
1476!
1477!--             xy-grid points above topography
1478                DO  k = nzb_s_outer(j,i), nz + 1
1479                   ngp_2dh_outer_l(k,sr) = ngp_2dh_outer_l(k,sr) + 1
1480                ENDDO
1481                DO  k = nzb_s_inner(j,i), nz + 1
1482                   ngp_2dh_s_inner_l(k,sr) = ngp_2dh_s_inner_l(k,sr) + 1
1483                ENDDO
1484!
1485!--             All grid points of the total domain above topography
1486                ngp_3d_inner_l(sr) = ngp_3d_inner_l(sr) + &
1487                                     ( nz - nzb_s_inner(j,i) + 2 )
1488             ENDIF
1489          ENDDO
1490       ENDDO
1491    ENDDO
1492
1493    sr = statistic_regions + 1
1494#if defined( __parallel )
1495    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
1496    CALL MPI_ALLREDUCE( ngp_2dh_l(0), ngp_2dh(0), sr, MPI_INTEGER, MPI_SUM,   &
1497                        comm2d, ierr )
1498    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
1499    CALL MPI_ALLREDUCE( ngp_2dh_outer_l(0,0), ngp_2dh_outer(0,0), (nz+2)*sr,  &
1500                        MPI_INTEGER, MPI_SUM, comm2d, ierr )
1501    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
1502    CALL MPI_ALLREDUCE( ngp_2dh_s_inner_l(0,0), ngp_2dh_s_inner(0,0),         &
1503                        (nz+2)*sr, MPI_INTEGER, MPI_SUM, comm2d, ierr )
1504    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
1505    CALL MPI_ALLREDUCE( ngp_3d_inner_l(0), ngp_3d_inner_tmp(0), sr, MPI_REAL, &
1506                        MPI_SUM, comm2d, ierr )
1507    ngp_3d_inner = INT( ngp_3d_inner_tmp, KIND = SELECTED_INT_KIND( 18 ) )
1508#else
1509    ngp_2dh         = ngp_2dh_l
1510    ngp_2dh_outer   = ngp_2dh_outer_l
1511    ngp_2dh_s_inner = ngp_2dh_s_inner_l
1512    ngp_3d_inner    = INT( ngp_3d_inner_l, KIND = SELECTED_INT_KIND( 18 ) )
1513#endif
1514
1515    ngp_3d = INT ( ngp_2dh, KIND = SELECTED_INT_KIND( 18 ) ) * &
1516             INT ( (nz + 2 ), KIND = SELECTED_INT_KIND( 18 ) )
1517
1518!
1519!-- Set a lower limit of 1 in order to avoid zero divisions in flow_statistics,
1520!-- buoyancy, etc. A zero value will occur for cases where all grid points of
1521!-- the respective subdomain lie below the surface topography
1522    ngp_2dh_outer   = MAX( 1, ngp_2dh_outer(:,:)   ) 
1523    ngp_3d_inner    = MAX( INT(1, KIND = SELECTED_INT_KIND( 18 )),            &
1524                           ngp_3d_inner(:) )
1525    ngp_2dh_s_inner = MAX( 1, ngp_2dh_s_inner(:,:) ) 
1526
1527    DEALLOCATE( ngp_2dh_l, ngp_2dh_outer_l, ngp_3d_inner_l, ngp_3d_inner_tmp )
1528
1529
1530 END SUBROUTINE init_3d_model
Note: See TracBrowser for help on using the repository browser.