source: palm/trunk/SOURCE/init_3d_model.f90 @ 372

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