source: palm/trunk/SOURCE/modules.f90 @ 418

Last change on this file since 418 was 412, checked in by raasch, 14 years ago

data asignments for dvrp arrays switched back to old settings due to runtime problems; type problem in mpi_waitall (poisfft_hybrid) fixed for mpi2 libraries

  • Property svn:keywords set to Id
File size: 63.5 KB
Line 
1 MODULE advection
2
3
4!------------------------------------------------------------------------------!
5! Current revisions:
6! -----------------
7! -var_ts: replaced by dots_max,
8! initial data assignments to some dvrp arrays changed due to error messages
9! from gfortran compiler
10! +large_scale_subsidence, ws_vertical_gradient, ws_vertical_gradient_level,
11! ws_vertical_gradient_level_ind, w_subs
12!
13! Branch revisions:
14! -----------------
15! Masked data output: + dt_domask, mask_01~20_x|y|z, mask_01~20_x|y|z_loop,
16! mask_scale|_x|y|z, masks, netcdf_format_mask[_av], skip_time_domask
17!
18! Former revisions:
19! -----------------
20! $Id: modules.f90 412 2009-12-14 07:14:46Z heinze $
21!
22! 388 2009-09-23 09:40:33Z raasch
23! +prho, prho_1
24! +bc_lr_cyc, bc_ns_cyc
25! +output_for_t0
26! translation error of actual -> current revisions fixed
27! +q* in dots_label, dots_unit. increased dots_num respectively
28! typographical error in dots_unit fixed
29! +clip_dvrp_*, cluster_size, color_interval, dvrpsize_interval, dvrp_overlap,
30! dvrp_total_overlap, groundplate_color, local_dvrserver_running, n*_dvrp,
31! interval_*_dvrp_prt, isosurface_color, particle_color, particle_dvrpsize,
32! topography color in dvrp_variables,
33! vertical_particle_advection is a 1d-array,
34! +canyon_height, canyon_width_x, canyon_width_y, canyon_wall_left,
35! canyon_wall_south, conserve_volume_flow_mode, coupling_start_time,
36! dp_external, dp_level_b, dp_level_ind_b, dp_smooth, dp_smooth_factor, dpdxy,
37! run_coupled, time_since_reference_point, u_bulk, v_bulk in control_parameters,
38! default value of grid_matching changed to strict
39! +shf_av, qsws_av
40!
41! 217 2008-12-09 18:00:48Z letzel
42! +topography_grid_convention
43! some dvrp-variables changed to single precision, variables for dvrp-mode
44! pathlines added, +target_id, abort_mode, message_string
45!
46! 197 2008-09-16 15:29:03Z raasch
47! allow 100 spectra levels instead of 10 for consistency with
48! define_netcdf_header, +canopy_heat_flux, cthf, lai,
49! +leaf_surface_concentration, scalar_exchange_coefficient, sec, sls
50! +hor_index_bounds, hor_index_bounds_previous_run, id_inflow, id_recycling,
51! inflow_damping_*, mean_inflow_profiles, numprocs_previous_run, nx_on_file,
52! ny_on_file, offset_ocean_*, recycling_plane, recycling_width, turbulent_inflow
53! -myid_char_14
54!
55! 138 2007-11-28 10:03:58Z letzel
56! +drag_coefficient, pch_index, lad_surface, lad_vertical_gradient,
57! lad_vertical_gradient_level, plant_canopy, lad, lad_s, lad_u, lad_v,
58! lad_w, cdc, lad_vertical_gradient_level_ind, canopy_mode
59! +dt_sort_particles, ngp_2dh_s_inner, time_sort_particles, flags,
60! wall_flags_1..10, wall_humidityflux(0:4), wall_qflux(0:4),
61! wall_salinityflux(0:4), wall_scalarflux(0:4)
62!
63! 108 2007-08-24 15:10:38Z letzel
64! +comm_inter, constant_top_momentumflux, coupling_char, coupling_mode,
65! coupling_mode_remote, c_u, c_v, c_w, dt_coupling, e_init, humidity_remote,
66! ngp_xy, nxlu, nysv, port_name, qswst_remote, terminate_coupled,
67! terminate_coupled_remote, time_coupling, top_momentumflux_u|v, type_xy,
68! uswst*, vswst*
69!
70! 97 2007-06-21 08:23:15Z raasch
71! +atmos_ocean_sign, ocean, r, + salinity variables
72! defaults of .._vertical_gradient_levels changed from -1.0 to -9999999.9
73! hydro_press renamed hyp, use_pt_reference renamed use_reference
74!
75! 89 2007-05-25 12:08:31Z raasch
76! +data_output_pr_user, max_pr_user, size of data_output_pr, dopr_index,
77! dopr_initial_index and dopr_unit enlarged,
78! var_hom and var_sum renamed pr_palm
79!
80! 82 2007-04-16 15:40:52Z raasch
81! +return_addres, return_username
82! Cpp-directive lcmuk renamed lc
83!
84! 75 2007-03-22 09:54:05Z raasch
85! +arrays precipitation_amount, precipitation_rate, precipitation_rate_av,
86! rif_wall, z0_av, +arrays u_m_l, u_m_r, etc. for radiation boundary conditions,
87! +loop_optimization, netcdf_64bit_3d, zu_s_inner, zw_w_inner, id_var_zusi_*,
88! id_var_zwwi_*, ts_value, u_nzb_p1_for_vfc, v_nzb_p1_for_vfc, pt_reference,
89! use_pt_reference, precipitation_amount_interval, revision
90! +age_m in particle_type, moisture renamed humidity,
91! -data_output_ts, dots_n, uvmean_outflow, uxrp, vynp,
92! arrays dots_label and dots_unit now dimensioned with dots_max,
93! setting of palm version moved to main program
94!
95! 37 2007-03-01 08:33:54Z raasch
96! +constant_top_heatflux, top_heatflux, use_top_fluxes, +arrays for top fluxes,
97! +nzt_diff, default of bc_pt_t renamed "initial_gradient"
98! Bugfix: p is not a pointer
99!
100! RCS Log replace by Id keyword, revision history cleaned up
101!
102! Revision 1.95  2007/02/11 13:18:30  raasch
103! version 3.1b (last under RCS control)
104!
105! Revision 1.1  1997/07/24 11:21:26  raasch
106! Initial revision
107!
108!
109! Description:
110! ------------
111! Definition of variables for special advection schemes
112!------------------------------------------------------------------------------!
113
114    REAL ::  spl_gamma_x, spl_gamma_y
115
116    REAL, DIMENSION(:), ALLOCATABLE   ::  aex, bex, dex, eex, spl_z_x, spl_z_y
117    REAL, DIMENSION(:,:), ALLOCATABLE ::  spl_tri_x, spl_tri_y, spl_tri_zu, &
118                                          spl_tri_zw
119
120    SAVE
121
122 END MODULE advection
123
124
125
126
127 MODULE array_kind
128
129!------------------------------------------------------------------------------!
130! Description:
131! ------------
132! Definition of type parameters (used for the definition of single or double
133! precision variables)
134!------------------------------------------------------------------------------!
135
136    INTEGER, PARAMETER ::  dpk = SELECTED_REAL_KIND( 12 ), &
137                           spk = SELECTED_REAL_KIND( 6 )
138
139    SAVE
140
141 END MODULE array_kind
142
143
144
145
146 MODULE arrays_3d
147
148!------------------------------------------------------------------------------!
149! Description:
150! ------------
151! Definition of all arrays defined on the computational grid
152!------------------------------------------------------------------------------!
153
154    USE array_kind
155
156    REAL, DIMENSION(:), ALLOCATABLE ::                                         &
157          ddzu, dd2zu, dzu, ddzw, dzw, hyp, inflow_damping_factor, km_damp_x,  &
158          km_damp_y, lad, l_grid, pt_init, q_init, rdf, sa_init, ug, u_init,   &
159          u_nzb_p1_for_vfc, vg, v_init, v_nzb_p1_for_vfc, w_subs, zu, zw
160
161    REAL, DIMENSION(:,:), ALLOCATABLE ::                                       &
162          c_u, c_v, c_w, dzu_mg, dzw_mg, f1_mg, f2_mg, f3_mg,                  &
163          mean_inflow_profiles, pt_slope_ref, qs, qswst_remote, ts, us, z0
164
165    REAL, DIMENSION(:,:), ALLOCATABLE, TARGET ::                               &
166          qsws_1, qsws_2, qswst_1, qswst_2, rif_1, rif_2, saswsb_1, saswst_1,  &
167          shf_1, shf_2, tswst_1, tswst_2, usws_1, usws_2, uswst_1, uswst_2,    &
168          vsws_1, vsws_2, vswst_1, vswst_2
169
170    REAL, DIMENSION(:,:), POINTER ::                                           &
171          qsws, qsws_m, qswst, qswst_m, rif, rif_m, saswsb, saswst, shf,       &
172          shf_m, tswst, tswst_m, usws, uswst, usws_m, uswst_m, vsws, vswst,    &
173          vsws_m, vswst_m
174
175    REAL, DIMENSION(:,:,:), ALLOCATABLE ::                                     &
176          canopy_heat_flux, cdc, d, diss, lad_s, lad_u, lad_v, lad_w, lai,     &
177          l_wall, sec, sls, tend, u_m_l, u_m_n, u_m_r, u_m_s, v_m_l, v_m_n,    &
178          v_m_r, v_m_s, w_m_l, w_m_n, w_m_r, w_m_s
179
180    REAL, DIMENSION(:,:,:), ALLOCATABLE, TARGET ::                             &
181          ql_v, ql_vp
182
183    REAL, DIMENSION(:,:,:), ALLOCATABLE, TARGET ::                             &
184          e_1, e_2, e_3, kh_1, kh_2, km_1, km_2, p, prho_1, pt_1, pt_2, pt_3,  &
185          q_1, q_2, q_3, ql_1, ql_2, rho_1, sa_1, sa_2, sa_3, u_1, u_2, u_3,   &
186          v_1, v_2, v_3, vpt_1, vpt_2, w_1, w_2, w_3
187
188    REAL, DIMENSION(:,:,:), POINTER ::                                         &
189          e, e_m, e_p, kh, kh_m, km, km_m, prho, pt, pt_m, pt_p, q, q_m, q_p,  &
190          ql, ql_c, rho, sa, sa_p, te_m, tpt_m, tq_m, tsa_m, tu_m, tv_m, tw_m, &
191          u, u_m, u_p, v, v_m, v_p, vpt, vpt_m, w, w_m, w_p
192
193    REAL, DIMENSION(:,:,:,:), ALLOCATABLE ::  rif_wall
194
195    SAVE
196
197 END MODULE arrays_3d
198
199
200
201
202 MODULE averaging
203
204!------------------------------------------------------------------------------!
205! Description:
206! ------------
207! Definition of variables needed for time-averaging of 2d/3d data
208!------------------------------------------------------------------------------!
209
210    REAL, DIMENSION(:,:), ALLOCATABLE ::  lwp_av, precipitation_rate_av,       &
211                                          qsws_av, shf_av,ts_av, us_av, z0_av
212
213    REAL, DIMENSION(:,:,:), ALLOCATABLE, TARGET :: &
214          e_av, p_av, pc_av, pr_av, pt_av, q_av, ql_av, ql_c_av, ql_v_av, &
215          ql_vp_av, qv_av, rho_av, s_av, sa_av, u_av, v_av, vpt_av, w_av
216
217 END MODULE averaging
218
219
220
221
222 MODULE cloud_parameters
223
224!------------------------------------------------------------------------------!
225! Description:
226! ------------
227! Definition of variables and constants for cloud physics
228!------------------------------------------------------------------------------!
229
230    REAL  ::  b_cond, cp = 1005.0, diff_coeff_l = 0.23E-4,                     &
231              effective_coll_efficiency, l_d_cp, l_d_r, l_d_rv, l_v = 2.5E+06, &
232              mass_of_solute, molecular_weight_of_solute,                      &
233              prec_time_const = 0.001, ql_crit = 0.0005, rho_l = 1.0E3,        &
234              r_d = 287.0, r_v = 461.51, thermal_conductivity_l = 2.43E-2
235
236    REAL, DIMENSION(:), ALLOCATABLE   ::  pt_d_t, t_d_pt
237
238    REAL, DIMENSION(:,:), ALLOCATABLE ::  precipitation_amount, &
239                                          precipitation_rate
240
241    SAVE
242
243 END MODULE cloud_parameters
244
245
246
247
248 MODULE constants
249
250!------------------------------------------------------------------------------!
251! Description:
252! ------------
253! Definition of general constants
254!------------------------------------------------------------------------------!
255
256    REAL    ::  pi = 3.141592654
257
258    SAVE
259
260 END MODULE constants
261
262
263
264
265 MODULE control_parameters
266
267!------------------------------------------------------------------------------!
268! Description:
269! ------------
270! Definition of parameters for program control
271!------------------------------------------------------------------------------!
272
273    TYPE plot_precision
274       CHARACTER (LEN=6) ::  variable
275       INTEGER           ::  precision
276    END TYPE plot_precision
277
278    TYPE(plot_precision), DIMENSION(100) ::  plot_3d_precision =               &
279                        (/ plot_precision( 'u', 2 ), plot_precision( 'v', 2 ), &
280                           plot_precision( 'w', 2 ), plot_precision( 'p', 5 ), &
281                           plot_precision( 'pt', 2 ),                          &
282                           ( plot_precision( ' ', 1 ), i9 = 1,95 ) /)
283
284    TYPE file_status
285       LOGICAL ::  opened, opened_before
286    END TYPE file_status
287
288    TYPE(file_status), DIMENSION(200) :: openfile = file_status(.FALSE.,.FALSE.)
289
290
291    INTEGER, PARAMETER :: mask_xyz_dimension = 100, max_masks = 20
292
293    CHARACTER (LEN=1)    ::  cycle_mg = 'w', timestep_reason = ' '
294    CHARACTER (LEN=2)    ::  coupling_char = ''
295    CHARACTER (LEN=5)    ::  write_binary = 'false'
296    CHARACTER (LEN=6)    ::  grid_matching = 'strict'
297    CHARACTER (LEN=8)    ::  run_date, run_time
298    CHARACTER (LEN=9)    ::  simulated_time_chr
299    CHARACTER (LEN=11)   ::  topography_grid_convention = ' '
300    CHARACTER (LEN=12)   ::  version = ' ', revision = ' '
301    CHARACTER (LEN=16)   ::  conserve_volume_flow_mode = 'default', &
302                             loop_optimization = 'default', &
303                             momentum_advec = 'pw-scheme', &
304                             psolver = 'poisfft', &
305                             scalar_advec = 'pw-scheme'
306    CHARACTER (LEN=20)   ::  bc_e_b = 'neumann', bc_lr = 'cyclic', &
307                             bc_ns = 'cyclic', bc_p_b = 'neumann', &
308                             bc_p_t = 'dirichlet', bc_pt_b = 'dirichlet', &
309                             bc_pt_t = 'initial_gradient', &
310                             bc_q_b = 'dirichlet', bc_q_t = 'neumann', &
311                             bc_s_b = 'dirichlet', bc_s_t = 'neumann', &
312                             bc_sa_t = 'neumann', &
313                             bc_uv_b = 'dirichlet', bc_uv_t = 'dirichlet', &
314                             canopy_mode = 'block', &
315                             coupling_mode = 'uncoupled', &
316                             coupling_mode_remote = 'uncoupled', &
317                             dissipation_1d = 'as_in_3d_model', &
318                             fft_method = 'system-specific', &
319                             mixing_length_1d = 'as_in_3d_model', &
320                             random_generator = 'numerical-recipes', &
321                             return_addres, return_username, &
322                             timestep_scheme = 'runge-kutta-3'
323    CHARACTER (LEN=40)   ::  avs_data_file, topography = 'flat'
324    CHARACTER (LEN=64)   ::  host = ' '
325    CHARACTER (LEN=80)   ::  log_message, run_identifier
326    CHARACTER (LEN=100)  ::  initializing_actions = ' ', run_description_header
327    CHARACTER (LEN=1000) ::  message_string = ' '
328
329    CHARACTER (LEN=7),  DIMENSION(100) ::  do3d_comp_prec = ' '
330    CHARACTER (LEN=10), DIMENSION(10)  ::  data_output_format = ' '
331    CHARACTER (LEN=11), DIMENSION(100) ::  data_output = ' ',    &
332                                           data_output_user = ' ', doav = ' '
333    CHARACTER (LEN=10), DIMENSION(100) ::  &
334         data_output_mask_01      = ' ', data_output_mask_02      = ' ',  &
335         data_output_mask_03      = ' ', data_output_mask_04      = ' ',  &
336         data_output_mask_05      = ' ', data_output_mask_06      = ' ',  &
337         data_output_mask_07      = ' ', data_output_mask_08      = ' ',  &
338         data_output_mask_09      = ' ', data_output_mask_10      = ' ',  &
339         data_output_mask_11      = ' ', data_output_mask_12      = ' ',  &
340         data_output_mask_13      = ' ', data_output_mask_14      = ' ',  &
341         data_output_mask_15      = ' ', data_output_mask_16      = ' ',  &
342         data_output_mask_17      = ' ', data_output_mask_18      = ' ',  &
343         data_output_mask_19      = ' ', data_output_mask_20      = ' ',  &
344         data_output_mask_user_01 = ' ', data_output_mask_user_02 = ' ',  &
345         data_output_mask_user_03 = ' ', data_output_mask_user_04 = ' ',  &
346         data_output_mask_user_05 = ' ', data_output_mask_user_06 = ' ',  &
347         data_output_mask_user_07 = ' ', data_output_mask_user_08 = ' ',  &
348         data_output_mask_user_09 = ' ', data_output_mask_user_10 = ' ',  &
349         data_output_mask_user_11 = ' ', data_output_mask_user_12 = ' ',  &
350         data_output_mask_user_13 = ' ', data_output_mask_user_14 = ' ',  &
351         data_output_mask_user_15 = ' ', data_output_mask_user_16 = ' ',  &
352         data_output_mask_user_17 = ' ', data_output_mask_user_18 = ' ',  &
353         data_output_mask_user_19 = ' ', data_output_mask_user_20 = ' '
354
355    CHARACTER (LEN=10), DIMENSION(300) ::  data_output_pr = ' '
356    CHARACTER (LEN=10), DIMENSION(200) ::  data_output_pr_user = ' '
357    CHARACTER (LEN=20), DIMENSION(50)  ::  netcdf_precision = ' '
358
359    CHARACTER (LEN=10), DIMENSION(max_masks,0:1,100) ::  domask = ' '
360    CHARACTER (LEN=10), DIMENSION(0:1,100) ::  do2d = ' ', do3d = ' '
361
362    INTEGER ::  abort_mode = 1, average_count_pr = 0, average_count_sp = 0, &
363                average_count_3d = 0, current_timestep_number = 0, &
364                dist_range = 0, disturbance_level_ind_b, &
365                disturbance_level_ind_t, doav_n = 0, dopr_n = 0, &
366                dopr_time_count = 0, dopts_time_count = 0, &
367                dosp_time_count = 0, dots_time_count = 0, &
368                do2d_xy_n = 0, do2d_xz_n = 0, do2d_yz_n = 0, do3d_avs_n = 0, &
369                dp_level_ind_b = 0, &
370                dvrp_filecount = 0, dz_stretch_level_index, gamma_mg, &
371                grid_level, ibc_e_b, ibc_p_b, ibc_p_t, ibc_pt_b, ibc_pt_t, &
372                ibc_q_b, ibc_q_t, ibc_sa_t, ibc_uv_b, ibc_uv_t, &
373                inflow_disturbance_begin = -1, inflow_disturbance_end = -1, &
374                intermediate_timestep_count, intermediate_timestep_count_max, &
375                iran = -1234567, last_dt_change = 0, masks = 0, &
376                maximum_grid_level, &
377                max_pr_user = 0, mgcycles = 0, mg_cycles = -1, &
378                mg_switch_to_pe0_level = 0, mid, ngsrb = 2, nsor = 20, &
379                nsor_ini = 100, n_sor, normalizing_region = 0, &
380                nz_do1d, nz_do3d = -9999, outflow_damping_width = -1, &
381                pch_index = 0, prt_time_count = 0, recycling_plane, runnr = 0, &
382                skip_do_avs = 0, terminate_coupled = 0, &
383                terminate_coupled_remote = 0, timestep_count = 0
384
385    INTEGER ::  dist_nxl(0:1), dist_nxr(0:1), dist_nyn(0:1), dist_nys(0:1), &
386                do2d_no(0:1) = 0, do2d_xy_time_count(0:1), &
387                do2d_xz_time_count(0:1), do2d_yz_time_count(0:1), &
388                do3d_no(0:1) = 0, do3d_time_count(0:1), &
389                domask_no(max_masks,0:1) = 0, domask_time_count(max_masks,0:1),&
390                lad_vertical_gradient_level_ind(10) = -9999, &
391                mask_size(max_masks,3) = -1, mask_size_l(max_masks,3) = -1, &
392                mask_start_l(max_masks,3) = -1, &
393                nc_format_mask(1:max_masks,0:1), &
394                netcdf_format_mask(1:max_masks) = 1, &
395                netcdf_format_mask_av(1:max_masks) = 1, &
396                pt_vertical_gradient_level_ind(10) = -9999, &
397                q_vertical_gradient_level_ind(10) = -9999, &
398                sa_vertical_gradient_level_ind(10) = -9999, &
399                section(100,3), section_xy(100) = -9999, &
400                section_xz(100) = -9999, section_yz(100) = -9999, &
401                ug_vertical_gradient_level_ind(10) = -9999, &
402                vg_vertical_gradient_level_ind(10) = -9999, &
403                ws_vertical_gradient_level_ind(10) = -9999
404
405    INTEGER, DIMENSION(:), ALLOCATABLE ::  grid_level_count
406
407    INTEGER, DIMENSION(:,:), ALLOCATABLE   ::  mask_i, mask_j, mask_k
408    INTEGER, DIMENSION(:,:), ALLOCATABLE   ::  &
409                mask_i_global, mask_j_global, mask_k_global
410
411    LOGICAL ::  adjust_mixing_length = .FALSE., avs_output = .FALSE., &
412                bc_lr_cyc =.TRUE., bc_ns_cyc = .TRUE., &
413                call_psolver_at_all_substeps = .TRUE., &
414                cloud_droplets = .FALSE., cloud_physics = .FALSE., &
415                conserve_volume_flow = .FALSE., constant_diffusion = .FALSE., &
416                constant_heatflux = .TRUE., constant_top_heatflux = .TRUE., &
417                constant_top_momentumflux = .FALSE., &
418                constant_top_salinityflux = .TRUE., &
419                constant_waterflux = .TRUE., create_disturbances = .TRUE., &
420                cut_spline_overshoot = .TRUE., &
421                data_output_2d_on_each_pe = .TRUE., do2d_at_begin = .FALSE., &
422                do3d_at_begin = .FALSE., do3d_compress = .FALSE., &
423                do_sum = .FALSE., dp_external = .FALSE., dp_smooth = .FALSE., &
424                dt_changed = .FALSE., dt_fixed = .FALSE., &
425                disturbance_created = .FALSE., &
426                first_call_advec_particles = .TRUE., &
427                force_print_header = .FALSE., format_parallel_io = .FALSE., &
428                galilei_transformation = .FALSE.,&
429                humidity = .FALSE., humidity_remote = .FALSE., &
430                inflow_l = .FALSE., inflow_n = .FALSE., &
431                inflow_r = .FALSE., inflow_s = .FALSE., &
432                iso2d_output = .FALSE., large_scale_subsidence = .FALSE., &
433                mg_switch_to_pe0 = .FALSE., &
434                netcdf_output = .FALSE., netcdf_64bit = .FALSE., &
435                netcdf_64bit_3d = .TRUE., ocean = .FALSE., &
436                outflow_l = .FALSE., outflow_n = .FALSE., outflow_r = .FALSE., &
437                outflow_s = .FALSE., passive_scalar = .FALSE., &
438                plant_canopy = .FALSE., &
439                prandtl_layer = .TRUE., precipitation = .FALSE., &
440                profil_output = .FALSE., radiation = .FALSE., &
441                random_heatflux = .FALSE., run_control_header = .FALSE., &
442                run_coupled = .TRUE., sloping_surface = .FALSE., &
443                stop_dt = .FALSE., terminate_run = .FALSE., &
444                turbulent_inflow = .FALSE., &
445                use_prior_plot1d_parameters = .FALSE., use_reference = .FALSE.,&
446                use_surface_fluxes = .FALSE., use_top_fluxes = .FALSE., &
447                use_ug_for_galilei_tr = .TRUE., use_upstream_for_tke = .FALSE.,&
448                wall_adjustment = .TRUE.
449
450    LOGICAL ::  data_output_xy(0:1) = .FALSE., data_output_xz(0:1) = .FALSE., &
451                data_output_yz(0:1) = .FALSE.
452
453    REAL ::  advected_distance_x = 0.0, advected_distance_y = 0.0, &
454             alpha_surface = 0.0, asselin_filter_factor = 0.1, &
455             atmos_ocean_sign = 1.0, &
456             averaging_interval = 0.0, averaging_interval_pr = 9999999.9, &
457             averaging_interval_sp = 9999999.9, bc_pt_t_val, bc_q_t_val, &
458             bottom_salinityflux = 0.0, &
459             building_height = 50.0, building_length_x = 50.0, &
460             building_length_y = 50.0, building_wall_left = 9999999.9, &
461             building_wall_south = 9999999.9, canyon_height = 50.0, &
462             canyon_width_x = 9999999.9, canyon_width_y = 9999999.9, &
463             canyon_wall_left = 9999999.9, canyon_wall_south = 9999999.9, &
464             cthf = 0.0, cfl_factor = -1.0, cos_alpha_surface, &
465             coupling_start_time, disturbance_amplitude = 0.25, &
466             disturbance_energy_limit = 0.01, &
467             disturbance_level_b = -9999999.9, &
468             disturbance_level_t = -9999999.9, &
469             dp_level_b = 0.0, drag_coefficient = 0.0, &
470             dt = -1.0, dt_averaging_input = 0.0, &
471             dt_averaging_input_pr = 9999999.9, dt_coupling = 9999999.9, &
472             dt_data_output = 9999999.9, &
473             dt_data_output_av = 9999999.9, dt_disturb = 9999999.9, &
474             dt_dopr = 9999999.9, dt_dopr_listing = 9999999.9, &
475             dt_dopts = 9999999.9, dt_dosp = 9999999.9, dt_dots = 9999999.9, &
476             dt_do2d_xy = 9999999.9, dt_do2d_xz = 9999999.9, &
477             dt_do2d_yz = 9999999.9, dt_do3d = 9999999.9, dt_dvrp = 9999999.9, &
478             dt_max = 20.0, dt_prel = 9999999.9, dt_restart = 9999999.9, &
479             dt_run_control = 60.0, dt_3d = -1.0, dz = -1.0, &
480             dz_max = 9999999.9, dz_stretch_factor = 1.08, &
481             dz_stretch_level = 100000.0, e_init = 0.0, e_min = 0.0, &
482             end_time = 0.0, &
483             f = 0.0, fs = 0.0, g = 9.81, inflow_damping_height = 9999999.9, &
484             inflow_damping_width = 9999999.9, kappa = 0.4, km_constant = -1.0,&
485             km_damp_max = -1.0, lad_surface = 0.0,  &
486             leaf_surface_concentration = 0.0, long_filter_factor = 0.0, &
487             mask_scale_x = 1.0, mask_scale_y = 1.0, mask_scale_z = 1.0, &
488             maximum_cpu_time_allowed = 0.0,  &
489             molecular_viscosity = 1.461E-5, &
490             old_dt = 1.0E-10, omega = 7.29212E-5, omega_sor = 1.8, &
491             overshoot_limit_e = 0.0, overshoot_limit_pt = 0.0, &
492             overshoot_limit_u = 0.0, overshoot_limit_v = 0.0, &
493             overshoot_limit_w = 0.0, particle_maximum_age = 9999999.9, &
494             phi = 55.0, prandtl_number = 1.0, &
495             precipitation_amount_interval = 9999999.9, prho_reference, &
496             pt_reference = 9999999.9, pt_slope_offset = 0.0, &
497             pt_surface = 300.0, pt_surface_initial_change = 0.0, &
498             q_surface = 0.0, q_surface_initial_change = 0.0, &
499             rayleigh_damping_factor = -1.0, rayleigh_damping_height = -1.0, &
500             recycling_width = 9999999.9, residual_limit = 1.0E-4, &
501             restart_time = 9999999.9, rho_reference, rho_surface, &
502             rif_max = 1.0, rif_min = -5.0, roughness_length = 0.1, &
503             sa_surface = 35.0, scalar_exchange_coefficient = 0.0, &
504             simulated_time = 0.0, simulated_time_at_begin, sin_alpha_surface, &
505             skip_time_data_output = 0.0, skip_time_data_output_av = 9999999.9,&
506             skip_time_dopr = 9999999.9, skip_time_dosp = 9999999.9, &
507             skip_time_do2d_xy = 9999999.9, skip_time_do2d_xz = 9999999.9, &
508             skip_time_do2d_yz = 9999999.9, skip_time_do3d = 9999999.9, &
509             surface_heatflux = 9999999.9, surface_pressure = 1013.25, &
510             surface_scalarflux = 0.0, surface_waterflux = 0.0, &
511             s_surface = 0.0, s_surface_initial_change = 0.0, &
512             termination_time_needed = -1.0, time_coupling = 0.0, &
513             time_disturb = 0.0, time_dopr = 0.0, time_dopr_av = 0.0, &
514             time_dopr_listing = 0.0, time_dopts = 0.0, time_dosp = 0.0, &
515             time_dosp_av = 0.0, time_dots = 0.0, time_do2d_xy = 0.0, &
516             time_do2d_xz = 0.0, time_do2d_yz = 0.0, time_do3d = 0.0, &
517             time_do_av = 0.0, time_do_sla = 0.0, time_dvrp = 0.0, &
518             time_prel = 0.0, time_restart = 9999999.9, time_run_control = 0.0,&
519             time_since_reference_point, top_heatflux = 9999999.9, &
520             top_momentumflux_u = 9999999.9, &
521             top_momentumflux_v = 9999999.9, top_salinityflux = 9999999.9, &
522             ug_surface = 0.0, u_bulk = 0.0, u_gtrans = 0.0, &
523             ups_limit_e = 0.0, ups_limit_pt = 0.0, ups_limit_u = 0.0, &
524             ups_limit_v = 0.0, ups_limit_w = 0.0, vg_surface = 0.0, &
525             v_bulk = 0.0, v_gtrans = 0.0, wall_adjustment_factor = 1.8, &
526             z_max_do1d = -1.0, z_max_do1d_normalized = -1.0, z_max_do2d = -1.0
527
528    REAL ::  do2d_xy_last_time(0:1) = -1.0, do2d_xz_last_time(0:1) = -1.0, &
529             do2d_yz_last_time(0:1) = -1.0, dpdxy(1:2) = 0.0, &
530             dt_domask(max_masks) = 9999999.9, lad_vertical_gradient(10) = 0.0,&
531             lad_vertical_gradient_level(10) = -9999999.9, &
532             mask_scale(3), &
533             pt_vertical_gradient(10) = 0.0, &
534             pt_vertical_gradient_level(10) = -9999999.9, &
535             q_vertical_gradient(10) = 0.0, &
536             q_vertical_gradient_level(10) = -1.0, &
537             s_vertical_gradient(10) = 0.0, &
538             s_vertical_gradient_level(10) = -1.0, &
539             sa_vertical_gradient(10) = 0.0, &
540             sa_vertical_gradient_level(10) = -9999999.9, &
541             skip_time_domask(max_masks) = 9999999.9, threshold(20) = 0.0, &
542             time_domask(max_masks) = 0.0, &
543             tsc(10) = (/ 0.0, 1.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0 /), &
544             ug_vertical_gradient(10) = 0.0, &
545             ug_vertical_gradient_level(10) = -9999999.9, &
546             vg_vertical_gradient(10) = 0.0, &
547             vg_vertical_gradient_level(10) = -9999999.9, &
548             volume_flow(1:2) = 0.0, volume_flow_area(1:2) = 0.0, &
549             volume_flow_initial(1:2) = 0.0, wall_heatflux(0:4) = 0.0, &
550             wall_humidityflux(0:4) = 0.0, wall_qflux(0:4) = 0.0, &
551             wall_salinityflux(0:4) = 0.0, wall_scalarflux(0:4) = 0.0, &
552             ws_vertical_gradient(10) = 0.0, &
553             ws_vertical_gradient_level(10) = -9999999.9
554
555    REAL, DIMENSION(:), ALLOCATABLE ::  dp_smooth_factor
556
557    REAL, DIMENSION(mask_xyz_dimension) ::  &
558       mask_01_x = -1.0, mask_02_x = -1.0, mask_03_x = -1.0, mask_04_x = -1.0, &
559       mask_05_x = -1.0, mask_06_x = -1.0, mask_07_x = -1.0, mask_08_x = -1.0, &
560       mask_09_x = -1.0, mask_10_x = -1.0, mask_11_x = -1.0, mask_12_x = -1.0, &
561       mask_13_x = -1.0, mask_14_x = -1.0, mask_15_x = -1.0, mask_16_x = -1.0, &
562       mask_17_x = -1.0, mask_18_x = -1.0, mask_19_x = -1.0, mask_20_x = -1.0, &
563       mask_01_y = -1.0, mask_02_y = -1.0, mask_03_y = -1.0, mask_04_y = -1.0, &
564       mask_05_y = -1.0, mask_06_y = -1.0, mask_07_y = -1.0, mask_08_y = -1.0, &
565       mask_09_y = -1.0, mask_10_y = -1.0, mask_11_y = -1.0, mask_12_y = -1.0, &
566       mask_13_y = -1.0, mask_14_y = -1.0, mask_15_y = -1.0, mask_16_y = -1.0, &
567       mask_17_y = -1.0, mask_18_y = -1.0, mask_19_y = -1.0, mask_20_y = -1.0, &
568       mask_01_z = -1.0, mask_02_z = -1.0, mask_03_z = -1.0, mask_04_z = -1.0, &
569       mask_05_z = -1.0, mask_06_z = -1.0, mask_07_z = -1.0, mask_08_z = -1.0, &
570       mask_09_z = -1.0, mask_10_z = -1.0, mask_11_z = -1.0, mask_12_z = -1.0, &
571       mask_13_z = -1.0, mask_14_z = -1.0, mask_15_z = -1.0, mask_16_z = -1.0, &
572       mask_17_z = -1.0, mask_18_z = -1.0, mask_19_z = -1.0, mask_20_z = -1.0
573    REAL, DIMENSION(3) ::  &
574       mask_01_x_loop = (/ -1.0, -1.0, 0.0 /), &
575       mask_02_x_loop = (/ -1.0, -1.0, 0.0 /), &
576       mask_03_x_loop = (/ -1.0, -1.0, 0.0 /), &
577       mask_04_x_loop = (/ -1.0, -1.0, 0.0 /), &
578       mask_05_x_loop = (/ -1.0, -1.0, 0.0 /), &
579       mask_06_x_loop = (/ -1.0, -1.0, 0.0 /), &
580       mask_07_x_loop = (/ -1.0, -1.0, 0.0 /), &
581       mask_08_x_loop = (/ -1.0, -1.0, 0.0 /), &
582       mask_09_x_loop = (/ -1.0, -1.0, 0.0 /), &
583       mask_10_x_loop = (/ -1.0, -1.0, 0.0 /), &
584       mask_11_x_loop = (/ -1.0, -1.0, 0.0 /), &
585       mask_12_x_loop = (/ -1.0, -1.0, 0.0 /), &
586       mask_13_x_loop = (/ -1.0, -1.0, 0.0 /), &
587       mask_14_x_loop = (/ -1.0, -1.0, 0.0 /), &
588       mask_15_x_loop = (/ -1.0, -1.0, 0.0 /), &
589       mask_16_x_loop = (/ -1.0, -1.0, 0.0 /), &
590       mask_17_x_loop = (/ -1.0, -1.0, 0.0 /), &
591       mask_18_x_loop = (/ -1.0, -1.0, 0.0 /), &
592       mask_19_x_loop = (/ -1.0, -1.0, 0.0 /), &
593       mask_20_x_loop = (/ -1.0, -1.0, 0.0 /), &
594       mask_01_y_loop = (/ -1.0, -1.0, 0.0 /), &
595       mask_02_y_loop = (/ -1.0, -1.0, 0.0 /), &
596       mask_03_y_loop = (/ -1.0, -1.0, 0.0 /), &
597       mask_04_y_loop = (/ -1.0, -1.0, 0.0 /), &
598       mask_05_y_loop = (/ -1.0, -1.0, 0.0 /), &
599       mask_06_y_loop = (/ -1.0, -1.0, 0.0 /), &
600       mask_07_y_loop = (/ -1.0, -1.0, 0.0 /), &
601       mask_08_y_loop = (/ -1.0, -1.0, 0.0 /), &
602       mask_09_y_loop = (/ -1.0, -1.0, 0.0 /), &
603       mask_10_y_loop = (/ -1.0, -1.0, 0.0 /), &
604       mask_11_y_loop = (/ -1.0, -1.0, 0.0 /), &
605       mask_12_y_loop = (/ -1.0, -1.0, 0.0 /), &
606       mask_13_y_loop = (/ -1.0, -1.0, 0.0 /), &
607       mask_14_y_loop = (/ -1.0, -1.0, 0.0 /), &
608       mask_15_y_loop = (/ -1.0, -1.0, 0.0 /), &
609       mask_16_y_loop = (/ -1.0, -1.0, 0.0 /), &
610       mask_17_y_loop = (/ -1.0, -1.0, 0.0 /), &
611       mask_18_y_loop = (/ -1.0, -1.0, 0.0 /), &
612       mask_19_y_loop = (/ -1.0, -1.0, 0.0 /), &
613       mask_20_y_loop = (/ -1.0, -1.0, 0.0 /), &
614       mask_01_z_loop = (/ -1.0, -1.0, 0.0 /), &
615       mask_02_z_loop = (/ -1.0, -1.0, 0.0 /), &
616       mask_03_z_loop = (/ -1.0, -1.0, 0.0 /), &
617       mask_04_z_loop = (/ -1.0, -1.0, 0.0 /), &
618       mask_05_z_loop = (/ -1.0, -1.0, 0.0 /), &
619       mask_06_z_loop = (/ -1.0, -1.0, 0.0 /), &
620       mask_07_z_loop = (/ -1.0, -1.0, 0.0 /), &
621       mask_08_z_loop = (/ -1.0, -1.0, 0.0 /), &
622       mask_09_z_loop = (/ -1.0, -1.0, 0.0 /), &
623       mask_10_z_loop = (/ -1.0, -1.0, 0.0 /), &
624       mask_11_z_loop = (/ -1.0, -1.0, 0.0 /), &
625       mask_12_z_loop = (/ -1.0, -1.0, 0.0 /), &
626       mask_13_z_loop = (/ -1.0, -1.0, 0.0 /), &
627       mask_14_z_loop = (/ -1.0, -1.0, 0.0 /), &
628       mask_15_z_loop = (/ -1.0, -1.0, 0.0 /), &
629       mask_16_z_loop = (/ -1.0, -1.0, 0.0 /), &
630       mask_17_z_loop = (/ -1.0, -1.0, 0.0 /), &
631       mask_18_z_loop = (/ -1.0, -1.0, 0.0 /), &
632       mask_19_z_loop = (/ -1.0, -1.0, 0.0 /), &
633       mask_20_z_loop = (/ -1.0, -1.0, 0.0 /)
634!
635!--    internal mask arrays ("mask,dimension,selection")
636       REAL, DIMENSION(:,:,:), ALLOCATABLE ::  mask, mask_loop
637
638    SAVE
639
640 END MODULE control_parameters
641
642
643
644
645 MODULE cpulog
646
647!------------------------------------------------------------------------------!
648! Description:
649! ------------
650! Definition of variables for cpu-time measurements
651!------------------------------------------------------------------------------!
652
653    REAL ::  initial_wallclock_time
654
655    TYPE logpoint
656       REAL               ::  isum, ivect, mean, mtime, mtimevec, sum, vector
657       INTEGER            ::  counts
658       CHARACTER (LEN=20) ::  place
659    END TYPE logpoint
660
661    TYPE(logpoint), DIMENSION(100) ::  log_point = logpoint( 0.0, 0.0, 0.0,   &
662                                       0.0, 0.0, 0.0, 0.0, 0, ' ' ),          &
663                                       log_point_s = logpoint( 0.0, 0.0, 0.0, &
664                                       0.0, 0.0, 0.0, 0.0, 0, ' ' )
665
666    SAVE
667
668 END MODULE cpulog
669
670
671
672
673 MODULE dvrp_variables
674
675!------------------------------------------------------------------------------!
676! Description:
677! ------------
678! Definition of variables used with dvrp-software
679!------------------------------------------------------------------------------!
680
681    CHARACTER (LEN=10) ::  dvrp_output = 'rtsp', particle_color = 'none', &
682                           particle_dvrpsize = 'none'
683
684    CHARACTER (LEN=20), DIMENSION(10) ::  mode_dvrp = &
685                                     (/ ( '                    ', i9 = 1,10 ) /)
686
687    CHARACTER (LEN=80) ::  dvrp_directory = 'default',                    &
688                           dvrp_file      = 'default',                    &
689                           dvrp_host      = 'origin.rvs.uni-hannover.de', &
690                           dvrp_password  = '********',                   &
691                           dvrp_username  = ' '
692
693    INTEGER ::  cluster_size = 1, dvrp_colortable_entries = 4,                 &
694                dvrp_colortable_entries_prt = 22, islice_dvrp,                 &
695                nx_dvrp, nxl_dvrp, nxr_dvrp, ny_dvrp, nyn_dvrp, nys_dvrp,      &
696                nz_dvrp, pathlines_fadeintime = 5, pathlines_fadeouttime = 5,  &
697                pathlines_linecount = 1000, pathlines_maxhistory = 40,         &
698                pathlines_wavecount = 10, pathlines_wavetime = 50,             &
699                vc_gradient_normals = 0, vc_mode = 0, vc_size_x = 2,           &
700                vc_size_y = 2, vc_size_z = 2
701
702    INTEGER, DIMENSION(10) ::  slicer_position_dvrp
703
704    LOGICAL ::  cyclic_dvrp = .FALSE., dvrp_overlap, dvrp_total_overlap, &
705                local_dvrserver_running, lock_steering_update = .FALSE., &
706                use_seperate_pe_for_dvrp_output = .FALSE.
707
708    REAL    ::  clip_dvrp_l = 9999999.9, clip_dvrp_n = 9999999.9, &
709                clip_dvrp_r = 9999999.9, clip_dvrp_s = 9999999.9, &
710                superelevation = 1.0, superelevation_x = 1.0,     &
711                superelevation_y = 1.0, vc_alpha = 38.0
712
713    REAL, DIMENSION(2) ::  color_interval = (/ 0.0, 1.0 /), &
714                           dvrpsize_interval = (/ 0.0, 1.0 /)
715
716    REAL, DIMENSION(3) ::  groundplate_color = (/ 0.0, 0.6, 0.0 /), &
717                           topography_color = (/ 0.8, 0.7, 0.6 /)
718
719#if defined( __decalpha )
720    REAL, DIMENSION(2,10)  ::  slicer_range_limits_dvrp = RESHAPE( (/       &
721                                -1.0, 1.0, -1.0, 1.0, -1.0, 1.0, -1.0, 1.0, &
722                                -1.0, 1.0, -1.0, 1.0, -1.0, 1.0, -1.0, 1.0, &
723                                -1.0, 1.0, -1.0, 1.0 /), (/ 2, 10 /) )
724
725    REAL, DIMENSION(3,10)  ::  isosurface_color = RESHAPE( (/                  &
726                                0.9, 0.9, 0.9,  0.8, 0.1, 0.1,  0.1, 0.1, 0.8, &
727                                0.1, 0.8, 0.1,  0.6, 0.1, 0.1,  0.1, 0.1, 0.6, &
728                                0.1, 0.6, 0.1,  0.4, 0.1, 0.1,  0.1, 0.1, 0.4, &
729                                0.1, 0.4, 0.1 /), (/ 3, 10 /) )
730
731    REAL(4), DIMENSION(2,100) ::  interval_values_dvrp, interval_h_dvrp =      &
732                                  RESHAPE( (/ 270.0, 225.0, 225.0, 180.0,      &
733                                               70.0,  25.0,  25.0, -25.0,      &
734                                              ( 0.0, i9 = 1, 192 ) /),         &
735                                           (/ 2, 100 /) ),                     &
736                                  interval_l_dvrp = 0.5, interval_s_dvrp = 1.0,&
737                                  interval_a_dvrp = 0.0,                       &
738                                  interval_values_dvrp_prt,                    &
739                                  interval_h_dvrp_prt = RESHAPE(               &
740                                  (/ 270.0, 225.0, 225.0, 180.0, 70.0, 25.0,   &
741                                     25.0, -25.0, ( 0.0, i9 = 1, 192 ) /),     &
742                                                  (/ 2, 100 /) ),              &
743                                  interval_l_dvrp_prt = 0.5,                   &
744                                  interval_s_dvrp_prt = 1.0,                   &
745                                  interval_a_dvrp_prt = 0.0
746#else
747    REAL, DIMENSION(2,10)     ::  slicer_range_limits_dvrp
748
749    REAL, DIMENSION(3,10)     ::  isosurface_color
750
751    REAL(4), DIMENSION(2,100) ::  interval_values_dvrp,                       &
752                                  interval_values_dvrp_prt, interval_h_dvrp,  &
753                                  interval_h_dvrp_prt, interval_l_dvrp = 0.5, &
754                                  interval_l_dvrp_prt = 0.5, interval_s_dvrp = 1.0, &
755                                  interval_s_dvrp_prt = 1.0, interval_a_dvrp = 0.0, &
756                                  interval_a_dvrp_prt = 0.0
757
758    DATA  slicer_range_limits_dvrp / -1.0, 1.0, -1.0, 1.0, -1.0, 1.0, &
759                                     -1.0, 1.0, -1.0, 1.0, -1.0, 1.0, &
760                                     -1.0, 1.0, -1.0, 1.0, -1.0, 1.0, &
761                                     -1.0, 1.0 /
762
763    DATA  isosurface_color / 0.9, 0.9, 0.9,  0.8, 0.1, 0.1,  0.1, 0.1, 0.8, &
764                             0.1, 0.8, 0.1,  0.6, 0.1, 0.1,  0.1, 0.1, 0.6, &
765                             0.1, 0.6, 0.1,  0.4, 0.1, 0.1,  0.1, 0.1, 0.4, &
766                             0.1, 0.4, 0.1 /
767
768    DATA  interval_h_dvrp / 270.0, 225.0, 225.0, 180.0, 70.0, 25.0, &
769                            25.0, -25.0, 192 * 0.0 /
770
771    DATA  interval_h_dvrp_prt / 270.0, 225.0, 225.0, 180.0, 70.0, 25.0, &
772                                25.0, -25.0, 192 * 0.0 /
773#endif
774
775    REAL(4), DIMENSION(:), ALLOCATABLE ::  xcoor_dvrp, ycoor_dvrp, zcoor_dvrp
776
777    TYPE steering
778       CHARACTER (LEN=20) ::  name
779       REAL(4)            ::  min, max
780       INTEGER            ::  imin, imax
781    END TYPE steering
782
783    TYPE(steering), DIMENSION(:), ALLOCATABLE ::  steering_dvrp
784
785    SAVE
786
787 END MODULE dvrp_variables
788
789
790
791
792 MODULE grid_variables
793
794!------------------------------------------------------------------------------!
795! Description:
796! ------------
797! Definition of grid spacings
798!------------------------------------------------------------------------------!
799
800    REAL ::  ddx, ddx2, dx = 1.0, dx2, ddy, ddy2, dy = 1.0, dy2
801
802    REAL, DIMENSION(:), ALLOCATABLE ::  ddx2_mg, ddy2_mg
803
804    REAL, DIMENSION(:,:), ALLOCATABLE ::  fwxm, fwxp, fwym, fwyp, fxm, fxp,   &
805                                          fym, fyp, wall_e_x, wall_e_y,       &
806                                          wall_u, wall_v, wall_w_x, wall_w_y, &
807                                          zu_s_inner, zw_w_inner
808
809    SAVE
810
811 END MODULE grid_variables
812
813
814
815
816 MODULE indices
817
818!------------------------------------------------------------------------------!
819! Description:
820! ------------
821! Definition of array bounds and number of gridpoints
822!------------------------------------------------------------------------------!
823
824    INTEGER ::  ngp_sums, nnx, nx = 0, nxa, nxl, nxlu, nxr, nxra, nx_on_file,  &
825                nny, ny = 0, nya, nyn, nyna, nys, nysv, ny_on_file, nnz,       &
826                nz = 0, nza, nzb, nzb_diff, nzt, nzta, nzt_diff
827
828    INTEGER, DIMENSION(:), ALLOCATABLE ::                                      &
829                ngp_2dh, ngp_3d, ngp_3d_inner,                                 &
830                nnx_pe, nny_pe, nxl_mg, nxr_mg, nyn_mg, nys_mg, nzt_mg
831
832    INTEGER, DIMENSION(:,:), ALLOCATABLE ::                                    &
833                ngp_2dh_outer, ngp_2dh_s_inner, mg_loc_ind, nzb_diff_s_inner,  &
834                nzb_diff_s_outer, nzb_diff_u, nzb_diff_v, nzb_inner, nzb_outer,&
835                nzb_s_inner, nzb_s_outer, nzb_u_inner, nzb_u_outer,            &
836                nzb_v_inner, nzb_v_outer, nzb_w_inner, nzb_w_outer, nzb_2d
837
838    INTEGER, DIMENSION(:,:,:), POINTER ::  flags
839
840    INTEGER, DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  wall_flags_1,           &
841                wall_flags_2, wall_flags_3, wall_flags_4, wall_flags_5,        &
842                wall_flags_6, wall_flags_7, wall_flags_8, wall_flags_9,        &
843                wall_flags_10
844
845    SAVE
846
847 END MODULE indices
848
849
850
851
852 MODULE interfaces
853
854!------------------------------------------------------------------------------!
855! Description:
856! ------------
857! Interfaces for special subroutines which use optional parameters
858!------------------------------------------------------------------------------!
859
860    INTERFACE
861
862       SUBROUTINE cpu_log( log_event, place, modus, barrierwait )
863
864          USE cpulog
865
866          CHARACTER (LEN=*)           ::  modus, place
867          CHARACTER (LEN=*), OPTIONAL ::  barrierwait
868          TYPE(logpoint)              ::  log_event
869
870       END SUBROUTINE cpu_log
871
872    END INTERFACE
873
874
875
876    INTERFACE
877
878       SUBROUTINE global_min_max ( i1, i2, j1, j2, k1, k2, feld, mode, wert, &
879                                   wert_ijk, wert1, wert1_ijk )
880          CHARACTER (LEN=*), INTENT(IN) ::  mode
881          INTEGER, INTENT(IN)           ::  i1, i2, j1, j2, k1, k2
882          INTEGER                       ::  wert_ijk(3)
883          INTEGER, OPTIONAL             ::  wert1_ijk(3)
884          REAL                          ::  wert
885          REAL, OPTIONAL                ::  wert1
886          REAL, INTENT(IN)              ::  feld(i1:i2,j1:j2,k1:k2)
887
888       END SUBROUTINE global_min_max
889
890    END INTERFACE
891
892    SAVE
893
894 END MODULE interfaces
895
896
897
898 MODULE pointer_interfaces
899
900!------------------------------------------------------------------------------!
901! Description:
902! ------------
903! Interfaces for subroutines with pointer arguments called in
904! prognostic_equations
905!------------------------------------------------------------------------------!
906
907    INTERFACE
908
909       SUBROUTINE advec_s_bc( sk, sk_char )
910
911          CHARACTER (LEN=*), INTENT(IN)   ::  sk_char
912          REAL, DIMENSION(:,:,:), POINTER ::  sk
913
914       END SUBROUTINE advec_s_bc
915
916    END INTERFACE
917
918
919    SAVE
920
921 END MODULE pointer_interfaces
922
923
924
925
926 MODULE model_1d
927
928!------------------------------------------------------------------------------!
929! Description:
930! ------------
931! Definition of variables for the 1D-model
932!------------------------------------------------------------------------------!
933
934    INTEGER ::  current_timestep_number_1d = 0, damp_level_ind_1d, &
935                last_dt_change_1d = 0 
936
937    LOGICAL ::  run_control_header_1d = .FALSE., stop_dt_1d = .FALSE. 
938
939    REAL ::     damp_level_1d = -1.0, dt_1d = 60.0, dt_max_1d = 300.0, &
940                dt_pr_1d = 9999999.9, dt_run_control_1d = 60.0, &
941                end_time_1d = 864000.0, old_dt_1d = 1.0E-10, &
942                qs1d, simulated_time_1d = 0.0, time_pr_1d = 0.0, &
943                time_run_control_1d = 0.0, ts1d, us1d, usws1d, usws1d_m, &
944                vsws1d, vsws1d_m, z01d
945
946
947    REAL, DIMENSION(:), ALLOCATABLE ::  e1d, e1d_m, e1d_p, kh1d, kh1d_m, km1d, &
948                                        km1d_m, l_black, l1d, l1d_m, rif1d,    &
949                                        te_e, te_em, te_u, te_um, te_v, te_vm, &
950                                        u1d, u1d_m, u1d_p, v1d, v1d_m, v1d_p
951
952    SAVE
953
954 END MODULE model_1d
955
956
957
958
959 MODULE netcdf_control
960
961!------------------------------------------------------------------------------!
962! Description:
963! ------------
964! Definition of parameters and variables for netcdf control.
965!------------------------------------------------------------------------------!
966
967    USE control_parameters
968#if defined( __netcdf )
969    USE netcdf
970#endif
971
972    INTEGER, PARAMETER ::  dopr_norm_num = 7, dopts_num = 26, dots_max = 100, &
973                           replace_num = 6
974
975    INTEGER ::  dots_num = 23
976
977    CHARACTER, DIMENSION( replace_num ) :: &
978                           replace_char = (/ '''', '"', '*', '/', '(', ')' /), &
979                           replace_by   = (/ 'p' , 'p', 's', 'o', '_', '_' /)
980
981    CHARACTER (LEN=6), DIMENSION(dopr_norm_num) ::  dopr_norm_names =   &
982         (/ 'wpt0  ', 'ws2   ', 'tsw2  ', 'ws3   ', 'ws2tsw', 'wstsw2', &
983            'z_i   ' /)
984
985    CHARACTER (LEN=6), DIMENSION(dopr_norm_num) ::  dopr_norm_longnames = &
986         (/ 'wpt0  ', 'w*2   ', 't*w2  ', 'w*3   ', 'w*2t*w', 'w*t*w2',   &
987            'z_i   ' /)
988
989    CHARACTER (LEN=7), DIMENSION(dopts_num) :: dopts_label = &
990          (/ 'tnpt   ', 'x_     ', 'y_     ', 'z_     ', 'z_abs  ', 'u      ', &
991             'v      ', 'w      ', 'u"     ', 'v"     ', 'w"     ', 'npt_up ', &
992             'w_up   ', 'w_down ', 'npt_max', 'npt_min', 'x*2    ', 'y*2    ', &
993             'z*2    ', 'u*2    ', 'v*2    ', 'w*2    ', 'u"2    ', 'v"2    ', &
994             'w"2    ', 'npt*2  ' /)
995
996    CHARACTER (LEN=7), DIMENSION(dopts_num) :: dopts_unit = &
997          (/ 'number ', 'm      ', 'm      ', 'm      ', 'm      ', 'm/s    ', &
998             'm/s    ', 'm/s    ', 'm/s    ', 'm/s    ', 'm/s    ', 'number ', &
999             'm/s    ', 'm/s    ', 'number ', 'number ', 'm2     ', 'm2     ', &
1000             'm2     ', 'm2/s2  ', 'm2/s2  ', 'm2/s2  ', 'm2/s2  ', 'm2/s2  ', &
1001             'm2/s2  ', 'number2' /)
1002
1003    CHARACTER (LEN=7), DIMENSION(dots_max) :: dots_label = &
1004          (/ 'E      ', 'E*     ', 'dt     ', 'u*     ', 'th*    ', 'umax   ', &
1005             'vmax   ', 'wmax   ', 'div_new', 'div_old', 'z_i_wpt', 'z_i_pt ', &
1006             'w*     ', 'w"pt"0 ', 'w"pt"  ', 'wpt    ', 'pt(0)  ', 'pt(zp) ', &
1007             'w"u"0  ', 'w"v"0  ', 'w"q"0  ', 'mo_L   ', 'q*     ',            &
1008             ( 'unknown', i9 = 1, dots_max-23 ) /)
1009
1010    CHARACTER (LEN=7), DIMENSION(dots_max) :: dots_unit = &
1011          (/ 'm2/s2  ', 'm2/s2  ', 's      ', 'm/s    ', 'K      ', 'm/s    ', &
1012             'm/s    ', 'm/s    ', 's-1    ', 's-1    ', 'm      ', 'm      ', &
1013             'm/s    ', 'K m/s  ', 'K m/s  ', 'K m/s  ', 'K      ', 'K      ', &
1014             'm2/s2  ', 'm2/s2  ', 'kg m/s ', 'm      ', 'kg/kg  ',            &
1015             ( 'unknown', i9 = 1, dots_max-23 ) /)
1016
1017    CHARACTER (LEN=7), DIMENSION(300) ::  dopr_unit = 'unknown'
1018
1019    CHARACTER (LEN=7), DIMENSION(0:1,100) ::  do2d_unit, do3d_unit
1020
1021    CHARACTER (LEN=16), DIMENSION(25) ::  prt_var_names = &
1022          (/ 'pt_age          ', 'pt_dvrp_size    ', 'pt_origin_x     ', &
1023             'pt_origin_y     ', 'pt_origin_z     ', 'pt_radius       ', &
1024             'pt_speed_x      ', 'pt_speed_y      ', 'pt_speed_z      ', &
1025             'pt_weight_factor', 'pt_x            ', 'pt_y            ', &
1026             'pt_z            ', 'pt_color        ', 'pt_group        ', &
1027             'pt_tailpoints   ', 'pt_tail_id      ', 'pt_density_ratio', &
1028             'pt_exp_arg      ', 'pt_exp_term     ', 'not_used        ', &
1029             'not_used        ', 'not_used        ', 'not_used        ', &
1030             'not_used        ' /)
1031
1032    CHARACTER (LEN=16), DIMENSION(25) ::  prt_var_units = &
1033          (/ 'seconds         ', 'meters          ', 'meters          ', &
1034             'meters          ', 'meters          ', 'meters          ', &
1035             'm/s             ', 'm/s             ', 'm/s             ', &
1036             'factor          ', 'meters          ', 'meters          ', &
1037             'meters          ', 'none            ', 'none            ', &
1038             'none            ', 'none            ', 'ratio           ', &
1039             'none            ', 'none            ', 'not_used        ', &
1040             'not_used        ', 'not_used        ', 'not_used        ', &
1041             'not_used        ' /)
1042
1043    INTEGER ::  id_dim_prtnum, id_dim_time_pr, id_dim_time_prt, &
1044                id_dim_time_pts, id_dim_time_sp, id_dim_time_ts, id_dim_x_sp, &
1045                id_dim_y_sp, id_dim_zu_sp, id_dim_zw_sp, id_set_pr, &
1046                id_set_prt, id_set_pts, id_set_sp, id_set_ts, id_var_prtnum, &
1047                id_var_rnop_prt, id_var_time_pr, id_var_time_prt, &
1048                id_var_time_pts, id_var_time_sp, id_var_time_ts, id_var_x_sp, &
1049                id_var_y_sp, id_var_zu_sp, id_var_zw_sp, nc_stat
1050
1051    INTEGER, DIMENSION(0:1) ::  id_dim_time_xy, id_dim_time_xz, &
1052                id_dim_time_yz, id_dim_time_3d, id_dim_x_xy, id_dim_xu_xy, &
1053                id_dim_x_xz, id_dim_xu_xz, id_dim_x_yz, id_dim_xu_yz, &
1054                id_dim_x_3d, id_dim_xu_3d, id_dim_y_xy, id_dim_yv_xy, &
1055                id_dim_y_xz, id_dim_yv_xz, id_dim_y_yz, id_dim_yv_yz, &
1056                id_dim_y_3d, id_dim_yv_3d, id_dim_zu_xy, id_dim_zu1_xy, &
1057                id_dim_zu_xz, id_dim_zu_yz, id_dim_zu_3d, id_dim_zw_xy, &
1058                id_dim_zw_xz, id_dim_zw_yz, id_dim_zw_3d, id_set_xy, &
1059                id_set_xz, id_set_yz, id_set_3d, id_var_ind_x_yz, &
1060                id_var_ind_y_xz, id_var_ind_z_xy, id_var_time_xy, &
1061                id_var_time_xz, id_var_time_yz, id_var_time_3d, id_var_x_xy, &
1062                id_var_xu_xy, id_var_x_xz, id_var_xu_xz, id_var_x_yz, &
1063                id_var_xu_yz, id_var_x_3d, id_var_xu_3d, id_var_y_xy, &
1064                id_var_yv_xy, id_var_y_xz, id_var_yv_xz, id_var_y_yz, &
1065                id_var_yv_yz, id_var_y_3d, id_var_yv_3d, id_var_zusi_xy, &
1066                id_var_zusi_3d, id_var_zu_xy, id_var_zu1_xy, id_var_zu_xz, &
1067                id_var_zu_yz, id_var_zu_3d, id_var_zwwi_xy, id_var_zwwi_3d, &
1068                id_var_zw_xy, id_var_zw_xz, id_var_zw_yz, id_var_zw_3d
1069
1070    INTEGER, DIMENSION(10)  ::  id_var_dospx, id_var_dospy
1071    INTEGER, DIMENSION(20)  ::  id_var_prt
1072    INTEGER, DIMENSION(50)  ::  nc_precision
1073    INTEGER, DIMENSION(dopr_norm_num) ::  id_var_norm_dopr
1074
1075    INTEGER, DIMENSION(dopts_num,0:10) ::  id_var_dopts
1076    INTEGER, DIMENSION(0:1,100)        ::  id_var_do2d, id_var_do3d
1077    INTEGER, DIMENSION(100,0:9)        ::  id_dim_z_pr, id_var_dopr, &
1078                                           id_var_z_pr
1079    INTEGER, DIMENSION(dots_max,0:9)   ::  id_var_dots
1080
1081!
1082!-- masked output
1083    CHARACTER (LEN=7), DIMENSION(max_masks,0:1,100) ::  domask_unit
1084
1085    LOGICAL ::  output_for_t0 = .FALSE.
1086
1087    INTEGER, DIMENSION(1:max_masks,0:1) ::  id_dim_time_mask, id_dim_x_mask, &
1088                id_dim_xu_mask, id_dim_y_mask, id_dim_yv_mask, id_dim_zu_mask, &
1089                id_dim_zw_mask, &
1090                id_set_mask, &
1091                id_var_time_mask, id_var_x_mask, id_var_xu_mask, &
1092                id_var_y_mask, id_var_yv_mask, id_var_zu_mask, id_var_zw_mask, &
1093                id_var_zusi_mask, id_var_zwwi_mask
1094
1095    INTEGER, DIMENSION(1:max_masks,0:1,100)         ::  id_var_domask
1096
1097    SAVE
1098
1099 END MODULE netcdf_control
1100
1101
1102
1103 MODULE particle_attributes
1104
1105!------------------------------------------------------------------------------!
1106! Description:
1107! ------------
1108! Definition of variables used to compute particle transport
1109!------------------------------------------------------------------------------!
1110
1111    USE array_kind
1112
1113    CHARACTER (LEN=15)  ::  bc_par_lr = 'cyclic',  bc_par_ns = 'cyclic', &
1114                            bc_par_b  = 'reflect', bc_par_t  = 'absorb'
1115
1116#if defined( __parallel )
1117    INTEGER ::  mpi_particle_type
1118#endif
1119    INTEGER ::  ibc_par_lr, ibc_par_ns, ibc_par_b, ibc_par_t,                  &
1120                iran_part = -1234567, maximum_number_of_particles = 1000,      &
1121                maximum_number_of_tailpoints = 100,                            &
1122                maximum_number_of_tails = 0,                                   &
1123                number_of_initial_particles = 0, number_of_particles = 0,      &
1124                number_of_particle_groups = 1, number_of_tails = 0,            &
1125                number_of_initial_tails = 0, offset_ocean_nzt = 0,             &
1126                offset_ocean_nzt_m1 = 0, particles_per_point = 1,              &
1127                particle_file_count = 0, skip_particles_for_tail = 100,        &
1128                total_number_of_particles, total_number_of_tails = 0
1129
1130    INTEGER, PARAMETER ::  max_number_of_particle_groups = 10
1131
1132    INTEGER, DIMENSION(:), ALLOCATABLE     ::  new_tail_id
1133    INTEGER, DIMENSION(:,:,:), ALLOCATABLE ::  prt_count, prt_start_index
1134
1135    LOGICAL ::  particle_advection = .FALSE., random_start_position = .FALSE., &
1136                read_particles_from_restartfile = .TRUE.,                      &
1137                uniform_particles = .TRUE., use_particle_tails = .FALSE.,      &
1138                use_sgs_for_particles = .FALSE.,                               &
1139                write_particle_statistics = .FALSE.
1140
1141    LOGICAL, DIMENSION(max_number_of_particle_groups) ::                       &
1142                vertical_particle_advection = .TRUE.
1143
1144    LOGICAL, DIMENSION(:), ALLOCATABLE ::  particle_mask, tail_mask
1145
1146    REAL    ::  c_0 = 3.0, dt_min_part = 0.0002, dt_sort_particles = 0.0,      &
1147                dt_write_particle_data = 9999999.9, dvrp_psize = 9999999.9,    &
1148                end_time_prel = 9999999.9, initial_weighting_factor = 1.0,     &
1149                maximum_tailpoint_age = 100000.0,                              &
1150                minimum_tailpoint_distance = 0.0,                              &
1151                particle_advection_start = 0.0, sgs_wfu_part = 0.3333333,      &
1152                sgs_wfv_part = 0.3333333, sgs_wfw_part = 0.3333333,            &
1153                time_sort_particles = 0.0, time_write_particle_data = 0.0
1154
1155    REAL, DIMENSION(max_number_of_particle_groups) ::  &
1156                density_ratio = 9999999.9, pdx = 9999999.9, pdy = 9999999.9, &
1157                pdz = 9999999.9, psb = 9999999.9, psl = 9999999.9,           &
1158                psn = 9999999.9, psr = 9999999.9, pss = 9999999.9,           &
1159                pst = 9999999.9, radius = 9999999.9
1160
1161    REAL, DIMENSION(:,:,:), ALLOCATABLE ::  particle_tail_coordinates
1162
1163
1164    TYPE particle_type
1165       SEQUENCE
1166       REAL    ::  age, age_m, dt_sum, dvrp_psize, e_m, origin_x, origin_y, &
1167                   origin_z, radius, speed_x, speed_x_sgs, speed_y,         &
1168                   speed_y_sgs, speed_z, speed_z_sgs, weight_factor, x, y, z
1169       INTEGER ::  color, group, tailpoints, tail_id
1170    END TYPE particle_type
1171
1172    TYPE(particle_type), DIMENSION(:), ALLOCATABLE ::  initial_particles, &
1173                                                       particles
1174
1175    TYPE particle_groups_type
1176       SEQUENCE
1177       REAL    ::  density_ratio, radius, exp_arg, exp_term
1178    END TYPE particle_groups_type
1179
1180    TYPE(particle_groups_type), DIMENSION(max_number_of_particle_groups) ::&
1181                   particle_groups
1182
1183    SAVE
1184
1185 END MODULE particle_attributes
1186
1187
1188
1189
1190
1191 MODULE pegrid
1192
1193!------------------------------------------------------------------------------!
1194! Description:
1195! ------------
1196! Definition of variables which define processor topology and the exchange of
1197! ghost point layers. This modules must be placed in all routines which contain
1198! MPI-calls.
1199!------------------------------------------------------------------------------!
1200
1201#if defined( __parallel )
1202#if defined( __lc )
1203    USE MPI
1204#else
1205    INCLUDE "mpif.h"
1206#endif
1207#endif
1208    CHARACTER(LEN=5)       ::  myid_char = ''
1209    INTEGER                ::  id_inflow = 0, id_recycling = 0, myid = 0,      &
1210                               target_id, npex = -1, npey = -1, numprocs = 1,  &
1211                               numprocs_previous_run = -1,                     &
1212                               tasks_per_node = -9999, threads_per_task = 1
1213
1214    INTEGER, DIMENSION(:,:), ALLOCATABLE ::  hor_index_bounds, &
1215                                             hor_index_bounds_previous_run
1216
1217#if defined( __parallel )
1218#if defined( __mpi2 )
1219    CHARACTER (LEN=MPI_MAX_PORT_NAME) ::  port_name
1220#endif
1221
1222    INTEGER ::  comm1dx, comm1dy, comm2d, comm_inter, comm_palm, ierr, myidx,  &
1223                myidy, ndim = 2, ngp_xy, ngp_y, pleft, pnorth, pright, psouth, &
1224                sendrecvcount_xy, sendrecvcount_yz, sendrecvcount_zx,          &
1225                sendrecvcount_zyd, sendrecvcount_yxd,                          &
1226                type_x, type_x_int, type_xy
1227
1228    INTEGER ::  ibuf(12), pcoord(2), pdims(2), status(MPI_STATUS_SIZE)
1229
1230    INTEGER, DIMENSION(:), ALLOCATABLE ::  ngp_yz, type_xz
1231
1232    LOGICAL ::  reorder = .TRUE.
1233    LOGICAL, DIMENSION(2) ::  cyclic = (/ .TRUE. , .TRUE. /), &
1234                              remain_dims
1235#endif
1236
1237    SAVE
1238
1239 END MODULE pegrid
1240
1241
1242
1243
1244 MODULE profil_parameter
1245
1246!------------------------------------------------------------------------------!
1247! Description:
1248! ------------
1249! Definition of variables which control PROFIL-output
1250!------------------------------------------------------------------------------!
1251
1252    INTEGER, PARAMETER ::  crmax = 100
1253
1254    CHARACTER (LEN=10), DIMENSION(100) ::  dopr_label = ' '
1255
1256    CHARACTER (LEN=10), DIMENSION(crmax) ::  cross_normalized_x = ' ', &
1257                                             cross_normalized_y = ' '
1258
1259    CHARACTER (LEN=20), DIMENSION(20) ::  cross_ts_profiles = &
1260                           (/ ' E E*               ', ' dt                 ', &
1261                              ' u* w*              ', ' th*                ', &
1262                              ' umax vmax wmax     ', ' div_old div_new    ', &
1263                              ' z_i_wpt z_i_pt     ', ' w"pt"0 w"pt" wpt   ', &
1264                              ' pt(0) pt(zp)       ', ' splux spluy spluz  ', &
1265                              ' L                  ',                         &
1266                            ( '                    ', i9 = 1, 9 ) /)
1267
1268    CHARACTER (LEN=40), DIMENSION(crmax) ::  cross_xtext = &
1269                           (/ 'windspeed in ms>->1         ', &
1270                              'pot. temperature in K       ', &
1271                              'heat flux in K ms>->1       ', &
1272                              'momentum flux in m>2s>2     ', &
1273                              'eddy diffusivity in m>2s>->1', &
1274                              'mixing length in m          ', &
1275                            ( '                            ', i9 = 1, 94 ) /)
1276
1277    CHARACTER (LEN=100), DIMENSION(crmax) ::  cross_profiles = &
1278                           (/ ' u v                           ', &
1279                              ' pt                            ', &
1280                              ' w"pt" w*pt* w*pt*BC wpt wptBC ', &
1281                              ' w"u" w*u* wu w"v" w*v* wv     ', &
1282                              ' km kh                         ', &
1283                              ' l                             ', &
1284                         ( '                               ', i9 = 1, 94 ) /)
1285
1286    INTEGER ::  profile_columns = 3, profile_rows = 2, profile_number = 0
1287
1288    INTEGER ::  cross_linecolors(100,crmax) = 1, &
1289                cross_linestyles(100,crmax) = 0, &
1290                cross_profile_numbers(100,crmax) = 0, &
1291                cross_pnc_local(crmax), cross_profile_number_count(crmax) = 0, &
1292                cross_ts_numbers(crmax,crmax) = 0, &
1293                cross_ts_number_count(crmax) = 0, dopr_crossindex(100) = 0, &
1294                dopr_index(300) = 0, dopr_initial_index(300) = 0, &
1295                dots_crossindex(100) = 0, dots_index(100) = 0, &
1296                linecolors(10) = (/ 2, 3, 4,  5, 7, 8, 12, 15, 16, 23 /), &
1297                linestyles(11) = (/ 0, 7, 3, 10, 4, 1,  9,  2,  5,  8, 6 /)
1298               
1299
1300    REAL ::  cross_normx_factor(100,crmax) = 1.0, &
1301             cross_normy_factor(100,crmax) = 1.0, &
1302             cross_ts_uymax(20) = &
1303                             (/ 999.999, 999.999, 999.999, 999.999, 999.999,   &
1304                                999.999, 999.999, 999.999, 999.999, 999.999,   &
1305                                999.999, 999.999, 999.999, 999.999, 999.999,   &
1306                                999.999, 999.999, 999.999, 999.999, 999.999 /),&
1307             cross_ts_uymax_computed(20) = 999.999, &
1308             cross_ts_uymin(20) = &
1309                             (/ 999.999, 999.999, 999.999,  -5.000, 999.999,   &
1310                                999.999,   0.000, 999.999, 999.999, 999.999,   &
1311                                999.999, 999.999, 999.999, 999.999, 999.999,   &
1312                                999.999, 999.999, 999.999, 999.999, 999.999 /),&
1313             cross_ts_uymin_computed(20) = 999.999, &
1314             cross_uxmax(crmax) = 0.0, cross_uxmax_computed(crmax) = -1.0, &
1315             cross_uxmax_normalized(crmax) = 0.0, &
1316             cross_uxmax_normalized_computed(crmax) = -1.0, &
1317             cross_uxmin(crmax) = 0.0, cross_uxmin_computed(crmax) =  1.0, &
1318             cross_uxmin_normalized(crmax) = 0.0, &
1319             cross_uxmin_normalized_computed(crmax) = 1.0, &
1320             cross_uymax(crmax), cross_uymin(crmax)
1321
1322    SAVE
1323
1324 END MODULE profil_parameter
1325
1326
1327
1328
1329 MODULE spectrum
1330
1331!------------------------------------------------------------------------------!
1332! Description:
1333! ------------
1334! Definition of quantities used for computing spectra
1335!------------------------------------------------------------------------------!
1336
1337    CHARACTER (LEN=6),  DIMENSION(1:5) ::  header_char = (/ 'PS(u) ', 'PS(v) ',&
1338                                           'PS(w) ', 'PS(pt)', 'PS(q) ' /)
1339    CHARACTER (LEN=2),  DIMENSION(10)  ::  spectra_direction = 'x'
1340    CHARACTER (LEN=10), DIMENSION(10)  ::  data_output_sp  = ' '
1341    CHARACTER (LEN=25), DIMENSION(1:5) ::  utext_char =                    &
1342                                           (/ '-power spectrum of u     ', &
1343                                              '-power spectrum of v     ', &
1344                                              '-power spectrum of w     ', &
1345                                              '-power spectrum of ^1185 ', &
1346                                              '-power spectrum of q     ' /)
1347    CHARACTER (LEN=39), DIMENSION(1:5) ::  ytext_char =                        &
1348                                 (/ 'k ^2236 ^2566^2569<u(k) in m>2s>->2    ', &
1349                                    'k ^2236 ^2566^2569<v(k) in m>2s>->2    ', &
1350                                    'k ^2236 ^2566^2569<w(k) in m>2s>->2    ', &
1351                                    'k ^2236 ^2566^2569<^1185(k) in m>2s>->2', &
1352                                    'k ^2236 ^2566^2569<q(k) in m>2s>->2    ' /)
1353
1354    INTEGER ::  klist_x = 0, klist_y = 0, n_sp_x = 0, n_sp_y = 0
1355
1356    INTEGER ::  comp_spectra_level(100) = 999999,                   &
1357                lstyles(100) = (/ 0, 7, 3, 10, 1, 4, 9, 2, 6, 8,    &
1358                                  0, 7, 3, 10, 1, 4, 9, 2, 6, 8,    &
1359                                  0, 7, 3, 10, 1, 4, 9, 2, 6, 8,    &
1360                                  0, 7, 3, 10, 1, 4, 9, 2, 6, 8,    &
1361                                  0, 7, 3, 10, 1, 4, 9, 2, 6, 8,    &
1362                                  0, 7, 3, 10, 1, 4, 9, 2, 6, 8,    &
1363                                  0, 7, 3, 10, 1, 4, 9, 2, 6, 8,    &
1364                                  0, 7, 3, 10, 1, 4, 9, 2, 6, 8,    &
1365                                  0, 7, 3, 10, 1, 4, 9, 2, 6, 8,    &
1366                                  0, 7, 3, 10, 1, 4, 9, 2, 6, 8 /), &
1367                plot_spectra_level(100) = 999999
1368
1369    REAL    ::  time_to_start_sp = 0.0
1370
1371    SAVE
1372
1373 END MODULE spectrum
1374
1375
1376
1377
1378 MODULE statistics
1379
1380!------------------------------------------------------------------------------!
1381! Description:
1382! ------------
1383! Definition of statistical quantities, e.g. global sums
1384!------------------------------------------------------------------------------!
1385
1386    CHARACTER (LEN=40) ::  region(0:9)
1387    INTEGER ::  pr_palm = 80, statistic_regions = 0
1388    INTEGER ::  u_max_ijk(3), v_max_ijk(3), w_max_ijk(3)
1389    LOGICAL ::  flow_statistics_called = .FALSE.
1390    REAL ::     u_max, v_max, w_max
1391    REAL, DIMENSION(:), ALLOCATABLE       ::  sums_divnew_l, sums_divold_l
1392    REAL, DIMENSION(:,:), ALLOCATABLE     ::  sums, sums_wsts_bc_l, ts_value
1393    REAL, DIMENSION(:,:,:), ALLOCATABLE   ::  hom_sum, rmask, spectrum_x, &
1394                                              spectrum_y, sums_l, sums_l_l, &
1395                                              sums_up_fraction_l
1396    REAL, DIMENSION(:,:,:,:), ALLOCATABLE ::  hom
1397
1398    SAVE
1399
1400 END MODULE statistics
1401
1402
1403
1404
1405 MODULE transpose_indices
1406
1407!------------------------------------------------------------------------------!
1408! Description:
1409! ------------
1410! Definition of indices for transposed arrays
1411!------------------------------------------------------------------------------!
1412
1413    INTEGER ::  nxl_y, nxl_yd, nxl_z, nxr_y, nxr_ya, nxr_yd, nxr_yda, nxr_z, &
1414                nxr_za, nyn_x, nyn_xa, nyn_z, nyn_za, nys_x, nys_z, nzb_x,   &
1415                nzb_y, nzb_yd, nzt_x, nzt_xa, nzt_y, nzt_ya, nzt_yd, nzt_yda
1416               
1417
1418    SAVE
1419
1420 END MODULE transpose_indices
Note: See TracBrowser for help on using the repository browser.