source: palm/trunk/SOURCE/time_integration.f90 @ 3159

Last change on this file since 3159 was 3159, checked in by sward, 6 years ago

Added multi agent system

  • Property svn:keywords set to Id
File size: 53.3 KB
Line 
1!> @file time_integration.f90
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2018 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! ------------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: time_integration.f90 3159 2018-07-20 11:20:01Z sward $
27! Added multi agent system
28!
29! 3042 2018-05-25 10:44:37Z schwenkel
30! Changed the name specific humidity to mixing ratio
31!
32! 3040 2018-05-25 10:22:08Z schwenkel
33! Fixed bug in IF statement
34! Ensure that the time when calling the radiation to be the time step of the
35! pre-calculated time when first calculate the positions of the sun
36!
37! 3004 2018-04-27 12:33:25Z Giersch
38! First call of flow_statistics has been removed. It is already called in
39! run_control itself
40!
41! 2984 2018-04-18 11:51:30Z hellstea
42! CALL pmci_ensure_nest_mass_conservation is removed (so far only commented out)
43! as seemingly unnecessary.
44!
45! 2941 2018-04-03 11:54:58Z kanani
46! Deduct spinup_time from RUN_CONTROL output of main 3d run
47! (use time_since_reference_point instead of simulated_time)
48!
49! 2938 2018-03-27 15:52:42Z suehring
50! Nesting of dissipation rate in case of RANS mode and TKE-e closure is applied
51!
52! 2936 2018-03-27 14:49:27Z suehring
53! Little formatting adjustment.
54!
55! 2817 2018-02-19 16:32:21Z knoop
56! Preliminary gust module interface implemented
57!
58! 2801 2018-02-14 16:01:55Z thiele
59! Changed lpm from subroutine to module.
60! Introduce particle transfer in nested models.
61!
62! 2776 2018-01-31 10:44:42Z Giersch
63! Variable use_synthetic_turbulence_generator has been abbreviated
64!
65! 2773 2018-01-30 14:12:54Z suehring
66! - Nesting for chemical species
67!
68! 2766 2018-01-22 17:17:47Z kanani
69! Removed preprocessor directive __chem
70!
71! 2718 2018-01-02 08:49:38Z maronga
72! Corrected "Former revisions" section
73!
74! 2696 2017-12-14 17:12:51Z kanani
75! - Change in file header (GPL part)
76! - Implementation of uv exposure model (FK)
77! - Moved vnest_boundary_conds_khkm from tcm_diffusivities to here (TG)
78! - renamed diffusivities to tcm_diffusivities (TG)
79! - implement prognostic equation for diss (TG)
80! - Moved/commented CALL to chem_emissions (FK)
81! - Added CALL to chem_emissions (FK)
82! - Implementation of chemistry module (FK)
83! - Calls for setting boundary conditions in USM and LSM (MS)
84! - Large-scale forcing with larger-scale models implemented (MS)
85! - Rename usm_radiation into radiation_interactions; merge with branch
86!   radiation (MS)
87! - added call for usm_green_heat_model for green building surfaces (RvT)
88! - added call for usm_temperature_near_surface for use in indoor model (RvT)
89!
90! 2617 2017-11-16 12:47:24Z suehring
91! Bugfix, assure that the reference state does not become zero.
92!
93! 2563 2017-10-19 15:36:10Z Giersch
94! Variable wind_turbine moved to module control_parameters
95!
96! 2365 2017-08-21 14:59:59Z kanani
97! Vertical grid nesting implemented (SadiqHuq)
98!
99! 2320 2017-07-21 12:47:43Z suehring
100! Set bottom boundary conditions after nesting interpolation and anterpolation
101!
102! 2299 2017-06-29 10:14:38Z maronga
103! Call of soil model adjusted
104!
105! 2292 2017-06-20 09:51:42Z schwenkel
106! Implementation of new microphysic scheme: cloud_scheme = 'morrison'
107! includes two more prognostic equations for cloud drop concentration (nc) 
108! and cloud water content (qc).
109!
110! 2271 2017-06-09 12:34:55Z sward
111! Start timestep message changed
112!
113! 2259 2017-06-08 09:09:11Z gronemeier
114! Implemented synthetic turbulence generator
115!
116! 2233 2017-05-30 18:08:54Z suehring
117!
118! 2232 2017-05-30 17:47:52Z suehring
119! Adjustments to new topography and surface concept
120! Modify passed parameters for disturb_field
121!
122! 2178 2017-03-17 11:07:39Z hellstea
123! Setting perturbations at all times near inflow boundary is removed
124! in case of nested boundaries
125!
126! 2174 2017-03-13 08:18:57Z maronga
127! Added support for nesting with cloud microphysics
128!
129! 2118 2017-01-17 16:38:49Z raasch
130! OpenACC directives and related code removed
131!
132! 2050 2016-11-08 15:00:55Z gronemeier
133! Implement turbulent outflow condition
134!
135! 2031 2016-10-21 15:11:58Z knoop
136! renamed variable rho to rho_ocean
137!
138! 2011 2016-09-19 17:29:57Z kanani
139! Flag urban_surface is now defined in module control_parameters,
140! removed commented CALLs of global_min_max.
141!
142! 2007 2016-08-24 15:47:17Z kanani
143! Added CALLs for new urban surface model
144!
145! 2000 2016-08-20 18:09:15Z knoop
146! Forced header and separation lines into 80 columns
147!
148! 1976 2016-07-27 13:28:04Z maronga
149! Simplified calls to radiation model
150!
151! 1960 2016-07-12 16:34:24Z suehring
152! Separate humidity and passive scalar
153!
154! 1957 2016-07-07 10:43:48Z suehring
155! flight module added
156!
157! 1919 2016-05-27 14:51:23Z raasch
158! Initial version of purely vertical nesting introduced.
159!
160! 1918 2016-05-27 14:35:57Z raasch
161! determination of time step moved to the end of the time step loop,
162! the first time step is now always calculated before the time step loop (i.e.
163! also in case of restart runs)
164!
165! 1914 2016-05-26 14:44:07Z witha
166! Added call for wind turbine model
167!
168! 1878 2016-04-19 12:30:36Z hellstea
169! Synchronization for nested runs rewritten
170!
171! 1853 2016-04-11 09:00:35Z maronga
172! Adjusted for use with radiation_scheme = constant
173!
174! 1849 2016-04-08 11:33:18Z hoffmann
175! Adapted for modularization of microphysics
176!
177! 1833 2016-04-07 14:23:03Z raasch
178! spectrum renamed spectra_mod, spectra related variables moved to spectra_mod
179!
180! 1831 2016-04-07 13:15:51Z hoffmann
181! turbulence renamed collision_turbulence
182!
183! 1822 2016-04-07 07:49:42Z hoffmann
184! icloud_scheme replaced by microphysics_*
185!
186! 1808 2016-04-05 19:44:00Z raasch
187! output message in case unscheduled radiation calls removed
188!
189! 1797 2016-03-21 16:50:28Z raasch
190! introduction of different datatransfer modes
191!
192! 1791 2016-03-11 10:41:25Z raasch
193! call of pmci_update_new removed
194!
195! 1786 2016-03-08 05:49:27Z raasch
196! +module spectrum
197!
198! 1783 2016-03-06 18:36:17Z raasch
199! switch back of netcdf data format for mask output moved to the mask output
200! routine
201!
202! 1781 2016-03-03 15:12:23Z raasch
203! some pmc calls removed at the beginning (before timeloop),
204! pmc initialization moved to the main program
205!
206! 1764 2016-02-28 12:45:19Z raasch
207! PMC_ACTIVE flags removed,
208! bugfix: nest synchronization after first call of timestep
209!
210! 1762 2016-02-25 12:31:13Z hellstea
211! Introduction of nested domain feature
212!
213! 1736 2015-12-04 08:56:33Z raasch
214! no perturbations added to total domain if energy limit has been set zero
215!
216! 1691 2015-10-26 16:17:44Z maronga
217! Added option for spin-ups without land surface and radiation models. Moved calls
218! for radiation and lan surface schemes.
219!
220! 1682 2015-10-07 23:56:08Z knoop
221! Code annotations made doxygen readable
222!
223! 1671 2015-09-25 03:29:37Z raasch
224! bugfix: ghostpoint exchange for array diss in case that sgs velocities are used
225! for particles
226!
227! 1585 2015-04-30 07:05:52Z maronga
228! Moved call of radiation scheme. Added support for RRTM
229!
230! 1551 2015-03-03 14:18:16Z maronga
231! Added interface for different radiation schemes.
232!
233! 1496 2014-12-02 17:25:50Z maronga
234! Added calls for the land surface model and radiation scheme
235!
236! 1402 2014-05-09 14:25:13Z raasch
237! location messages modified
238!
239! 1384 2014-05-02 14:31:06Z raasch
240! location messages added
241!
242! 1380 2014-04-28 12:40:45Z heinze
243! CALL of nudge_ref added
244! bc_pt_t_val and bc_q_t_val are updated in case nudging is used
245!
246! 1365 2014-04-22 15:03:56Z boeske
247! Reset sums_ls_l to zero at each timestep
248! +sums_ls_l
249! Calculation of reference state (previously in subroutine calc_mean_profile)
250
251! 1342 2014-03-26 17:04:47Z kanani
252! REAL constants defined as wp-kind
253!
254! 1320 2014-03-20 08:40:49Z raasch
255! ONLY-attribute added to USE-statements,
256! kind-parameters added to all INTEGER and REAL declaration statements,
257! kinds are defined in new module kinds,
258! old module precision_kind is removed,
259! revision history before 2012 removed,
260! comment fields (!:) to be used for variable explanations added to
261! all variable declaration statements
262! 1318 2014-03-17 13:35:16Z raasch
263! module interfaces removed
264!
265! 1308 2014-03-13 14:58:42Z fricke
266! +netcdf_data_format_save
267! For masked data, parallel netcdf output is not tested so far, hence
268! netcdf_data_format is switched back to non-paralell output.
269!
270! 1276 2014-01-15 13:40:41Z heinze
271! Use LSF_DATA also in case of Dirichlet bottom boundary condition for scalars
272!
273! 1257 2013-11-08 15:18:40Z raasch
274! acc-update-host directive for timestep removed
275!
276! 1241 2013-10-30 11:36:58Z heinze
277! Generalize calc_mean_profile for wider use
278! Determine shf and qsws in dependence on data from LSF_DATA
279! Determine ug and vg in dependence on data from LSF_DATA
280! 1221 2013-09-10 08:59:13Z raasch
281! host update of arrays before timestep is called
282!
283! 1179 2013-06-14 05:57:58Z raasch
284! mean profiles for reference state are only calculated if required,
285! small bugfix for background communication
286!
287! 1171 2013-05-30 11:27:45Z raasch
288! split of prognostic_equations deactivated (comment lines), for the time being
289!
290! 1128 2013-04-12 06:19:32Z raasch
291! asynchronous transfer of ghost point data realized for acc-optimized version:
292! prognostic_equations are first called two times for those points required for
293! the left-right and north-south exchange, respectively, and then for the
294! remaining points,
295! those parts requiring global communication moved from prognostic_equations to
296! here
297!
298! 1115 2013-03-26 18:16:16Z hoffmann
299! calculation of qr and nr is restricted to precipitation
300!
301! 1113 2013-03-10 02:48:14Z raasch
302! GPU-porting of boundary conditions,
303! openACC directives updated
304! formal parameter removed from routine boundary_conds
305!
306! 1111 2013-03-08 23:54:10Z raasch
307! +internal timestep counter for cpu statistics added,
308! openACC directives updated
309!
310! 1092 2013-02-02 11:24:22Z raasch
311! unused variables removed
312!
313! 1065 2012-11-22 17:42:36Z hoffmann
314! exchange of diss (dissipation rate) in case of turbulence = .TRUE. added
315!
316! 1053 2012-11-13 17:11:03Z hoffmann
317! exchange of ghost points for nr, qr added
318!
319! 1036 2012-10-22 13:43:42Z raasch
320! code put under GPL (PALM 3.9)
321!
322! 1019 2012-09-28 06:46:45Z raasch
323! non-optimized version of prognostic_equations removed
324!
325! 1015 2012-09-27 09:23:24Z raasch
326! +call of prognostic_equations_acc
327!
328! 1001 2012-09-13 14:08:46Z raasch
329! all actions concerning leapfrog- and upstream-spline-scheme removed
330!
331! 849 2012-03-15 10:35:09Z raasch
332! advec_particles renamed lpm, first_call_advec_particles renamed first_call_lpm
333!
334! 825 2012-02-19 03:03:44Z raasch
335! wang_collision_kernel renamed wang_kernel
336!
337! Revision 1.1  1997/08/11 06:19:04  raasch
338! Initial revision
339!
340!
341! Description:
342! ------------
343!> Integration in time of the model equations, statistical analysis and graphic
344!> output
345!------------------------------------------------------------------------------!
346 SUBROUTINE time_integration
347 
348
349    USE advec_ws,                                                              &
350        ONLY:  ws_statistics
351
352    USE arrays_3d,                                                             &
353        ONLY:  diss, diss_p, dzu, e, e_p, nc, nc_p, nr, nr_p, prho, pt, pt_p, pt_init, &
354               q_init, q, qc, qc_p, ql, ql_c, ql_v, ql_vp, qr, qr_p, q_p,      &
355               ref_state, rho_ocean, s, s_p, sa_p, tend, u, u_p, v, vpt,       &
356               v_p, w, w_p
357
358    USE calc_mean_profile_mod,                                                 &
359        ONLY:  calc_mean_profile
360
361    USE chemistry_model_mod,                                                   &
362        ONLY:  chem_emissions, chem_species
363
364    USE chem_modules,                                                          &
365        ONLY:  nspec 
366
367    USE control_parameters,                                                    &
368        ONLY:  advected_distance_x, advected_distance_y, air_chemistry,        &
369               average_count_3d, averaging_interval, averaging_interval_pr,    &
370               bc_lr_cyc, bc_ns_cyc, bc_pt_t_val,                              &
371               bc_q_t_val, call_psolver_at_all_substeps, cloud_droplets,       &
372               cloud_physics, constant_flux_layer, constant_heatflux,          &
373               create_disturbances, dopr_n, constant_diffusion, coupling_mode, &
374               coupling_start_time, current_timestep_number,                   &
375               disturbance_created, disturbance_energy_limit, dist_range,      &
376               do_sum, dt_3d, dt_averaging_input, dt_averaging_input_pr,       &
377               dt_coupling, dt_data_output_av, dt_disturb, dt_do2d_xy,         &
378               dt_do2d_xz, dt_do2d_yz, dt_do3d, dt_domask,dt_dopts, dt_dopr,   &
379               dt_dopr_listing, dt_dots, dt_dvrp, dt_run_control, end_time,    &
380               first_call_lpm, first_call_mas, forcing, galilei_transformation,&
381               humidity, intermediate_timestep_count,                          &
382               intermediate_timestep_count_max, land_surface,                  &
383               large_scale_forcing, loop_optimization, lsf_surf, lsf_vert,     &
384               masks, microphysics_morrison, microphysics_seifert, mid,        &
385               nest_domain, neutral, nr_timesteps_this_run, nudging,           &
386               ocean, passive_scalar, prho_reference, pt_reference,            &
387               pt_slope_offset, random_heatflux, rans_mode,                    &
388               rans_tke_e, run_coupled, simulated_time, simulated_time_chr,    &
389               skip_time_do2d_xy, skip_time_do2d_xz, skip_time_do2d_yz,        &
390               skip_time_do3d, skip_time_domask, skip_time_dopr,               &
391               skip_time_data_output_av, sloping_surface,                      &
392               stop_dt, terminate_coupled, terminate_run, timestep_scheme,     &
393               time_coupling, time_do2d_xy, time_do2d_xz, time_do2d_yz,        &
394               time_do3d, time_domask, time_dopr, time_dopr_av,                &
395               time_dopr_listing, time_dopts, time_dosp, time_dosp_av,         &
396               time_dots, time_do_av, time_do_sla, time_disturb, time_dvrp,    &
397               time_run_control, time_since_reference_point,                   &
398               turbulent_inflow, turbulent_outflow, urban_surface,             &
399               use_initial_profile_as_reference,                               &
400               use_single_reference_value, uv_exposure, u_gtrans, v_gtrans,    &
401               virtual_flight, wind_turbine, ws_scheme_mom, ws_scheme_sca
402
403    USE cpulog,                                                                &
404        ONLY:  cpu_log, log_point, log_point_s
405
406    USE flight_mod,                                                            &
407        ONLY:  flight_measurement
408
409    USE gust_mod,                                                              &
410        ONLY:  gust_actions, gust_module_enabled
411
412    USE indices,                                                               &
413        ONLY:  nbgp, nx, nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg, nzb, nzt
414
415    USE interaction_droplets_ptq_mod,                                          &
416        ONLY:  interaction_droplets_ptq
417
418    USE interfaces
419
420    USE kinds
421
422    USE land_surface_model_mod,                                                &
423        ONLY:  lsm_boundary_condition, lsm_energy_balance, lsm_soil_model,     &
424               skip_time_do_lsm
425
426    USE lsf_nudging_mod,                                                       &
427        ONLY:  calc_tnudge, ls_forcing_surf, ls_forcing_vert, nudge_ref,       &
428               forcing_bc, forcing_bc_mass_conservation
429
430    USE netcdf_data_input_mod,                                                 &
431        ONLY:  force, netcdf_data_input_lsf
432
433    USE microphysics_mod,                                                      &
434        ONLY: collision_turbulence
435
436    USE multi_agent_system_mod,                                                &
437        ONLY:  agents_active, multi_agent_system, multi_agent_system_start
438
439    USE particle_attributes,                                                   &
440        ONLY:  particle_advection, particle_advection_start,                   &
441               use_sgs_for_particles, wang_kernel
442
443    USE pegrid
444
445    USE pmc_interface,                                                         &
446        ONLY:  nested_run, nesting_mode, pmci_boundary_conds, pmci_datatrans,  &
447               pmci_ensure_nest_mass_conservation, pmci_synchronize
448
449    USE progress_bar,                                                          &
450        ONLY:  finish_progress_bar, output_progress_bar
451
452    USE prognostic_equations_mod,                                              &
453        ONLY:  prognostic_equations_cache, prognostic_equations_vector
454
455    USE radiation_model_mod,                                                   &
456        ONLY: dt_radiation, force_radiation_call, radiation, radiation_control,&
457              radiation_interaction, radiation_interactions,                   &
458              skip_time_do_radiation, time_radiation
459
460    USE spectra_mod,                                                           &
461        ONLY: average_count_sp, averaging_interval_sp, calc_spectra, dt_dosp,  &
462              skip_time_dosp
463
464    USE statistics,                                                            &
465        ONLY:  flow_statistics_called, hom, pr_palm, sums_ls_l, u_max,         &
466               u_max_ijk, v_max, v_max_ijk, w_max, w_max_ijk
467
468    USE surface_layer_fluxes_mod,                                              &
469        ONLY:  surface_layer_fluxes
470
471    USE surface_mod,                                                           &
472        ONLY:  surf_def_h, surf_lsm_h, surf_usm_h
473
474    USE turbulence_closure_mod,                                                &
475        ONLY:  tcm_diffusivities, production_e_init
476
477    USE urban_surface_mod,                                                     &
478        ONLY:  usm_boundary_condition, usm_material_heat_model,                &
479               usm_material_model,                                             &
480               usm_surface_energy_balance, usm_green_heat_model,               &
481               usm_temperature_near_surface
482
483    USE synthetic_turbulence_generator_mod,                                    &
484        ONLY:  stg_main, use_syn_turb_gen
485
486    USE user_actions_mod,                                                      &
487        ONLY:  user_actions
488
489    USE uv_exposure_model_mod,                                                 &
490        ONLY:  uvem_calc_exposure
491
492    USE wind_turbine_model_mod,                                                &
493        ONLY:  wtm_forces
494
495    USE lpm_mod,                                                               &
496        ONLY:  lpm
497
498    USE vertical_nesting_mod,                                                  &
499        ONLY:  vnested, vnest_anterpolate, vnest_anterpolate_e,                &
500               vnest_boundary_conds, vnest_boundary_conds_khkm,                & 
501               vnest_deallocate, vnest_init, vnest_init_fine,                  &
502               vnest_start_time
503
504    IMPLICIT NONE
505
506    CHARACTER (LEN=9) ::  time_to_string          !<
507    INTEGER(iwp)      ::  it
508    INTEGER(iwp)      ::  lsp
509    INTEGER(iwp)      ::  n
510
511
512    REAL(wp) ::  dt_3d_old  !< temporary storage of timestep to be used for
513                            !< steering of run control output interval
514    REAL(wp) ::  tsrp_org   !< original value of time_since_reference_point
515!
516!-- At beginning determine the first time step
517    CALL timestep
518!
519!-- Synchronize the timestep in case of nested run.
520    IF ( nested_run )  THEN
521!
522!--    Synchronization by unifying the time step.
523!--    Global minimum of all time-steps is used for all.
524       CALL pmci_synchronize
525    ENDIF
526
527!
528!-- Determine and print out the run control quantities before the first time
529!-- step of this run. For the initial run, some statistics (e.g. divergence)
530!-- need to be determined first --> CALL flow_statistics at the beginning of
531!-- run_control
532    CALL run_control
533!
534!-- Data exchange between coupled models in case that a call has been omitted
535!-- at the end of the previous run of a job chain.
536    IF ( coupling_mode /= 'uncoupled'  .AND.  run_coupled .AND. .NOT. vnested)  THEN
537!
538!--    In case of model termination initiated by the local model the coupler
539!--    must not be called because this would again cause an MPI hang.
540       DO WHILE ( time_coupling >= dt_coupling  .AND.  terminate_coupled == 0 )
541          CALL surface_coupler
542          time_coupling = time_coupling - dt_coupling
543       ENDDO
544       IF (time_coupling == 0.0_wp  .AND.                                      &
545           time_since_reference_point < dt_coupling )                          &
546       THEN
547          time_coupling = time_since_reference_point
548       ENDIF
549    ENDIF
550
551#if defined( __dvrp_graphics )
552!
553!-- Time measurement with dvrp software 
554    CALL DVRP_LOG_EVENT( 2, current_timestep_number )
555#endif
556
557    CALL location_message( 'starting timestep-sequence', .TRUE. )
558!
559!-- Start of the time loop
560    DO  WHILE ( simulated_time < end_time  .AND.  .NOT. stop_dt  .AND. &
561                .NOT. terminate_run )
562
563       CALL cpu_log( log_point_s(10), 'timesteps', 'start' )
564!
565!--    Vertical nesting: initialize fine grid
566       IF ( vnested ) THEN
567          IF ( .NOT. vnest_init  .AND.  simulated_time >= vnest_start_time )  THEN
568             CALL cpu_log( log_point(80), 'vnest_init', 'start' )
569             CALL vnest_init_fine
570             vnest_init = .TRUE.
571             CALL cpu_log( log_point(80), 'vnest_init', 'stop' )
572          ENDIF
573       ENDIF
574!
575!--    Determine ug, vg and w_subs in dependence on data from external file
576!--    LSF_DATA
577       IF ( large_scale_forcing .AND. lsf_vert )  THEN
578           CALL ls_forcing_vert ( simulated_time )
579           sums_ls_l = 0.0_wp
580       ENDIF
581
582!
583!--    Set pt_init and q_init to the current profiles taken from
584!--    NUDGING_DATA
585       IF ( nudging )  THEN
586           CALL nudge_ref ( simulated_time )
587!
588!--        Store temperature gradient at the top boundary for possible Neumann
589!--        boundary condition
590           bc_pt_t_val = ( pt_init(nzt+1) - pt_init(nzt) ) / dzu(nzt+1)
591           bc_q_t_val  = ( q_init(nzt+1) - q_init(nzt) ) / dzu(nzt+1)
592       ENDIF
593!
594!--    If forcing by larger-scale models is applied, check if new data
595!--    at domain boundaries need to be read.
596       IF ( forcing )  THEN
597          IF ( force%time(force%tind_p) <= simulated_time )                    &
598             CALL netcdf_data_input_lsf
599       ENDIF
600
601!
602!--    Execute the gust module actions
603       IF ( gust_module_enabled )  THEN
604          CALL gust_actions( 'before_timestep' )
605       ENDIF
606
607!
608!--    Execute the user-defined actions
609       CALL user_actions( 'before_timestep' )
610
611!
612!--    Calculate forces by wind turbines
613       IF ( wind_turbine )  THEN
614
615          CALL cpu_log( log_point(55), 'wind_turbine', 'start' )
616
617          CALL wtm_forces
618
619          CALL cpu_log( log_point(55), 'wind_turbine', 'stop' )
620
621       ENDIF       
622       
623!
624!--    Start of intermediate step loop
625       intermediate_timestep_count = 0
626       DO  WHILE ( intermediate_timestep_count < &
627                   intermediate_timestep_count_max )
628
629          intermediate_timestep_count = intermediate_timestep_count + 1
630
631!
632!--       Set the steering factors for the prognostic equations which depend
633!--       on the timestep scheme
634          CALL timestep_scheme_steering
635
636!
637!--       Calculate those variables needed in the tendency terms which need
638!--       global communication
639          IF ( .NOT. use_single_reference_value  .AND. &
640               .NOT. use_initial_profile_as_reference )  THEN
641!
642!--          Horizontally averaged profiles to be used as reference state in
643!--          buoyancy terms (WARNING: only the respective last call of
644!--          calc_mean_profile defines the reference state!)
645             IF ( .NOT. neutral )  THEN
646                CALL calc_mean_profile( pt, 4 )
647                ref_state(:)  = hom(:,1,4,0) ! this is used in the buoyancy term
648             ENDIF
649             IF ( ocean )  THEN
650                CALL calc_mean_profile( rho_ocean, 64 )
651                ref_state(:)  = hom(:,1,64,0)
652             ENDIF
653             IF ( humidity )  THEN
654                CALL calc_mean_profile( vpt, 44 )
655                ref_state(:)  = hom(:,1,44,0)
656             ENDIF
657!
658!--          Assure that ref_state does not become zero at any level
659!--          ( might be the case if a vertical level is completely occupied
660!--            with topography ).
661             ref_state = MERGE( MAXVAL(ref_state), ref_state,                  &
662                                ref_state == 0.0_wp )
663          ENDIF
664
665          IF ( .NOT. constant_diffusion )  CALL production_e_init
666          IF ( ( ws_scheme_mom .OR. ws_scheme_sca )  .AND.  &
667               intermediate_timestep_count == 1 )  CALL ws_statistics
668!
669!--       In case of nudging calculate current nudging time scale and horizontal
670!--       means of u, v, pt and q
671          IF ( nudging )  THEN
672             CALL calc_tnudge( simulated_time )
673             CALL calc_mean_profile( u, 1 )
674             CALL calc_mean_profile( v, 2 )
675             CALL calc_mean_profile( pt, 4 )
676             CALL calc_mean_profile( q, 41 )
677          ENDIF
678
679!
680!--       Solve the prognostic equations. A fast cache optimized version with
681!--       only one single loop is used in case of Piascek-Williams advection
682!--       scheme. NEC vector machines use a different version, because
683!--       in the other versions a good vectorization is prohibited due to
684!--       inlining problems.
685          IF ( loop_optimization == 'cache' )  THEN
686             CALL prognostic_equations_cache
687          ELSEIF ( loop_optimization == 'vector' )  THEN
688             CALL prognostic_equations_vector
689          ENDIF
690
691!
692!--       Particle transport/physics with the Lagrangian particle model
693!--       (only once during intermediate steps, because it uses an Euler-step)
694!--       ### particle model should be moved before prognostic_equations, in order
695!--       to regard droplet interactions directly
696          IF ( particle_advection  .AND.                         &
697               simulated_time >= particle_advection_start  .AND. &
698               intermediate_timestep_count == 1 )  THEN
699             CALL lpm
700             first_call_lpm = .FALSE.
701          ENDIF
702
703!
704!--       Interaction of droplets with temperature and mixing ratio.
705!--       Droplet condensation and evaporation is calculated within
706!--       advec_particles.
707          IF ( cloud_droplets  .AND.  &
708               intermediate_timestep_count == intermediate_timestep_count_max )&
709          THEN
710             CALL interaction_droplets_ptq
711          ENDIF
712
713!
714!--       Movement of agents in multi agent system
715          IF ( agents_active  .AND.                                            &
716               simulated_time >= multi_agent_system_start  .AND.               &
717               intermediate_timestep_count == 1 )  THEN
718             CALL multi_agent_system
719             first_call_mas = .FALSE.
720          ENDIF
721
722!
723!--       Exchange of ghost points (lateral boundary conditions)
724          CALL cpu_log( log_point(26), 'exchange-horiz-progn', 'start' )
725
726          CALL exchange_horiz( u_p, nbgp )
727          CALL exchange_horiz( v_p, nbgp )
728          CALL exchange_horiz( w_p, nbgp )
729          CALL exchange_horiz( pt_p, nbgp )
730          IF ( .NOT. constant_diffusion )  CALL exchange_horiz( e_p, nbgp )
731          IF ( rans_tke_e  .OR.  wang_kernel  .OR.  collision_turbulence       &
732               .OR.  use_sgs_for_particles )  THEN
733             IF ( rans_tke_e )  THEN
734                CALL exchange_horiz( diss_p, nbgp )
735             ELSE
736                CALL exchange_horiz( diss, nbgp )
737             ENDIF
738          ENDIF
739          IF ( ocean )  THEN
740             CALL exchange_horiz( sa_p, nbgp )
741             CALL exchange_horiz( rho_ocean, nbgp )
742             CALL exchange_horiz( prho, nbgp )
743          ENDIF
744          IF ( humidity )  THEN
745             CALL exchange_horiz( q_p, nbgp )
746             IF ( cloud_physics .AND. microphysics_morrison )  THEN
747                CALL exchange_horiz( qc_p, nbgp )
748                CALL exchange_horiz( nc_p, nbgp )
749             ENDIF
750             IF ( cloud_physics .AND. microphysics_seifert )  THEN
751                CALL exchange_horiz( qr_p, nbgp )
752                CALL exchange_horiz( nr_p, nbgp )
753             ENDIF
754          ENDIF
755          IF ( cloud_droplets )  THEN
756             CALL exchange_horiz( ql, nbgp )
757             CALL exchange_horiz( ql_c, nbgp )
758             CALL exchange_horiz( ql_v, nbgp )
759             CALL exchange_horiz( ql_vp, nbgp )
760          ENDIF
761          IF ( passive_scalar )  CALL exchange_horiz( s_p, nbgp )
762          IF ( air_chemistry )  THEN
763             DO  n = 1, nspec     
764                CALL exchange_horiz( chem_species(n)%conc_p, nbgp ) 
765             ENDDO
766          ENDIF
767
768          CALL cpu_log( log_point(26), 'exchange-horiz-progn', 'stop' )
769
770!
771!--       Boundary conditions for the prognostic quantities (except of the
772!--       velocities at the outflow in case of a non-cyclic lateral wall)
773          CALL boundary_conds
774!
775!--       Swap the time levels in preparation for the next time step.
776          CALL swap_timelevel
777
778!
779!--       Vertical nesting: Interpolate fine grid data to the coarse grid
780          IF ( vnest_init ) THEN
781             CALL cpu_log( log_point(81), 'vnest_anterpolate', 'start' )
782             CALL vnest_anterpolate
783             CALL cpu_log( log_point(81), 'vnest_anterpolate', 'stop' )
784          ENDIF
785
786          IF ( nested_run )  THEN
787
788             CALL cpu_log( log_point(60), 'nesting', 'start' )
789!
790!--          Domain nesting. The data transfer subroutines pmci_parent_datatrans
791!--          and pmci_child_datatrans are called inside the wrapper
792!--          subroutine pmci_datatrans according to the control parameters
793!--          nesting_mode and nesting_datatransfer_mode.
794!--          TO_DO: why is nesting_mode given as a parameter here?
795             CALL pmci_datatrans( nesting_mode )
796
797             IF ( TRIM( nesting_mode ) == 'two-way' .OR.                       &
798                  nesting_mode == 'vertical' )  THEN
799!
800!--             Exchange_horiz is needed for all parent-domains after the
801!--             anterpolation
802                CALL exchange_horiz( u, nbgp )
803                CALL exchange_horiz( v, nbgp )
804                CALL exchange_horiz( w, nbgp )
805                IF ( .NOT. neutral )  CALL exchange_horiz( pt, nbgp )
806
807                IF ( humidity )  THEN
808
809                   CALL exchange_horiz( q, nbgp )
810
811                   IF ( cloud_physics  .AND.  microphysics_morrison )  THEN
812                       CALL exchange_horiz( qc, nbgp )
813                       CALL exchange_horiz( nc, nbgp )
814                   ENDIF
815                   IF ( cloud_physics  .AND.  microphysics_seifert )  THEN
816                       CALL exchange_horiz( qr, nbgp )
817                       CALL exchange_horiz( nr, nbgp )
818                   ENDIF
819
820                ENDIF
821
822                IF ( passive_scalar )  CALL exchange_horiz( s, nbgp )
823                IF ( .NOT. constant_diffusion )  CALL exchange_horiz( e, nbgp )
824
825                IF ( .NOT. constant_diffusion  .AND.  rans_mode  .AND.         &
826                                                      rans_tke_e )             &
827                   CALL exchange_horiz( diss, nbgp )
828
829                IF ( air_chemistry )  THEN
830                   DO  n = 1, nspec     
831                      CALL exchange_horiz( chem_species(n)%conc, nbgp ) 
832                   ENDDO
833                ENDIF
834
835             ENDIF
836!
837!--          Set boundary conditions again after interpolation and anterpolation.
838             CALL pmci_boundary_conds
839!
840!--          Correct the w top-BC in nest domains to ensure mass conservation.
841!--          This action must never be done for the root domain. Vertical
842!--          nesting implies mass conservation.
843!--          Commented out April 18, 2018 as seemingly unnecessary.
844!--          Will later be completely removed.
845!--             IF ( nest_domain )  THEN
846!--                CALL pmci_ensure_nest_mass_conservation
847!--             ENDIF
848
849             CALL cpu_log( log_point(60), 'nesting', 'stop' )
850
851          ENDIF
852
853!
854!--       Temperature offset must be imposed at cyclic boundaries in x-direction
855!--       when a sloping surface is used
856          IF ( sloping_surface )  THEN
857             IF ( nxl ==  0 )  pt(:,:,nxlg:nxl-1) = pt(:,:,nxlg:nxl-1) - &
858                                                    pt_slope_offset
859             IF ( nxr == nx )  pt(:,:,nxr+1:nxrg) = pt(:,:,nxr+1:nxrg) + &
860                                                    pt_slope_offset
861          ENDIF
862
863!
864!--       Impose a turbulent inflow using the recycling method
865          IF ( turbulent_inflow )  CALL  inflow_turbulence
866
867!
868!--       Impose a turbulent inflow using synthetic generated turbulence
869          IF ( use_syn_turb_gen )  CALL  stg_main
870
871!
872!--       Set values at outflow boundary using the special outflow condition
873          IF ( turbulent_outflow )  CALL  outflow_turbulence
874
875!
876!--       Impose a random perturbation on the horizontal velocity field
877          IF ( create_disturbances  .AND.                                      &
878               ( call_psolver_at_all_substeps  .AND.                           &
879               intermediate_timestep_count == intermediate_timestep_count_max )&
880          .OR. ( .NOT. call_psolver_at_all_substeps  .AND.                     &
881               intermediate_timestep_count == 1 ) )                            &
882          THEN
883             time_disturb = time_disturb + dt_3d
884             IF ( time_disturb >= dt_disturb )  THEN
885                IF ( disturbance_energy_limit /= 0.0_wp  .AND.                 &
886                     hom(nzb+5,1,pr_palm,0) < disturbance_energy_limit )  THEN
887                   CALL disturb_field( 'u', tend, u )
888                   CALL disturb_field( 'v', tend, v )
889                ELSEIF ( ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )            &
890                     .AND. .NOT. nest_domain  .AND.  .NOT.  forcing )  THEN
891!
892!--                Runs with a non-cyclic lateral wall need perturbations
893!--                near the inflow throughout the whole simulation
894                   dist_range = 1
895                   CALL disturb_field( 'u', tend, u )
896                   CALL disturb_field( 'v', tend, v )
897                   dist_range = 0
898                ENDIF
899                time_disturb = time_disturb - dt_disturb
900             ENDIF
901          ENDIF
902
903!
904!--       Map forcing data derived from larger scale model onto domain
905!--       boundaries.
906          IF ( forcing  .AND.  intermediate_timestep_count ==                  &
907                               intermediate_timestep_count_max  )  THEN
908             CALL forcing_bc
909!
910!--          Moreover, ensure mass conservation
911             CALL forcing_bc_mass_conservation
912          ENDIF
913
914!
915!--       Reduce the velocity divergence via the equation for perturbation
916!--       pressure.
917          IF ( intermediate_timestep_count == 1  .OR. &
918                call_psolver_at_all_substeps )  THEN
919
920             IF (  vnest_init ) THEN
921!
922!--             Compute pressure in the CG, interpolate top boundary conditions
923!--             to the FG and then compute pressure in the FG
924                IF ( coupling_mode == 'vnested_crse' )  CALL pres
925
926                CALL cpu_log( log_point(82), 'vnest_bc', 'start' )
927                CALL vnest_boundary_conds
928                CALL cpu_log( log_point(82), 'vnest_bc', 'stop' )
929 
930                IF ( coupling_mode == 'vnested_fine' )  CALL pres
931
932!--             Anterpolate TKE, satisfy Germano Identity
933                CALL cpu_log( log_point(83), 'vnest_anter_e', 'start' )
934                CALL vnest_anterpolate_e
935                CALL cpu_log( log_point(83), 'vnest_anter_e', 'stop' )
936
937             ELSE
938
939                CALL pres
940
941             ENDIF
942
943          ENDIF
944
945!
946!--       If required, compute liquid water content
947          IF ( cloud_physics )  THEN
948             CALL calc_liquid_water_content
949          ENDIF
950!
951!--       If required, compute virtual potential temperature
952          IF ( humidity )  THEN
953             CALL compute_vpt 
954          ENDIF 
955
956!
957!--       Compute the diffusion quantities
958          IF ( .NOT. constant_diffusion )  THEN
959
960!
961!--          Determine surface fluxes shf and qsws and surface values
962!--          pt_surface and q_surface in dependence on data from external
963!--          file LSF_DATA respectively
964             IF ( ( large_scale_forcing .AND. lsf_surf ) .AND. &
965                 intermediate_timestep_count == intermediate_timestep_count_max )&
966             THEN
967                CALL ls_forcing_surf( simulated_time )
968             ENDIF
969
970!
971!--          First the vertical (and horizontal) fluxes in the surface
972!--          (constant flux) layer are computed
973             IF ( constant_flux_layer )  THEN
974                CALL cpu_log( log_point(19), 'surface_layer_fluxes', 'start' )
975                CALL surface_layer_fluxes
976                CALL cpu_log( log_point(19), 'surface_layer_fluxes', 'stop' )
977             ENDIF
978!
979!--          If required, solve the energy balance for the surface and run soil
980!--          model. Call for horizontal as well as vertical surfaces
981             IF ( land_surface .AND. time_since_reference_point >= skip_time_do_lsm)  THEN
982
983                CALL cpu_log( log_point(54), 'land_surface', 'start' )
984!
985!--             Call for horizontal upward-facing surfaces
986                CALL lsm_energy_balance( .TRUE., -1 )
987                CALL lsm_soil_model( .TRUE., -1, .TRUE. )
988!
989!--             Call for northward-facing surfaces
990                CALL lsm_energy_balance( .FALSE., 0 )
991                CALL lsm_soil_model( .FALSE., 0, .TRUE. )
992!
993!--             Call for southward-facing surfaces
994                CALL lsm_energy_balance( .FALSE., 1 )
995                CALL lsm_soil_model( .FALSE., 1, .TRUE. )
996!
997!--             Call for eastward-facing surfaces
998                CALL lsm_energy_balance( .FALSE., 2 )
999                CALL lsm_soil_model( .FALSE., 2, .TRUE. )
1000!
1001!--             Call for westward-facing surfaces
1002                CALL lsm_energy_balance( .FALSE., 3 )
1003                CALL lsm_soil_model( .FALSE., 3, .TRUE. )
1004!
1005!--             At the end, set boundary conditons for potential temperature
1006!--             and humidity after running the land-surface model. This
1007!--             might be important for the nesting, where arrays are transfered.
1008                CALL lsm_boundary_condition
1009
1010                CALL cpu_log( log_point(54), 'land_surface', 'stop' )
1011             ENDIF
1012!
1013!--          If required, solve the energy balance for urban surfaces and run
1014!--          the material heat model
1015             IF (urban_surface) THEN
1016                CALL cpu_log( log_point(74), 'urban_surface', 'start' )
1017                CALL usm_surface_energy_balance
1018                IF ( usm_material_model )  THEN
1019                   CALL usm_green_heat_model
1020                   CALL usm_material_heat_model
1021                ENDIF
1022
1023                CALL usm_temperature_near_surface
1024!
1025!--             At the end, set boundary conditons for potential temperature
1026!--             and humidity after running the urban-surface model. This
1027!--             might be important for the nesting, where arrays are transfered.
1028                CALL usm_boundary_condition
1029
1030                CALL cpu_log( log_point(74), 'urban_surface', 'stop' )
1031             ENDIF
1032!
1033!--          Compute the diffusion coefficients
1034             CALL cpu_log( log_point(17), 'diffusivities', 'start' )
1035             IF ( .NOT. humidity ) THEN
1036                IF ( ocean )  THEN
1037                   CALL tcm_diffusivities( prho, prho_reference )
1038                ELSE
1039                   CALL tcm_diffusivities( pt, pt_reference )
1040                ENDIF
1041             ELSE
1042                CALL tcm_diffusivities( vpt, pt_reference )
1043             ENDIF
1044             CALL cpu_log( log_point(17), 'diffusivities', 'stop' )
1045!
1046!--          Vertical nesting: set fine grid eddy viscosity top boundary condition
1047             IF ( vnest_init )  CALL vnest_boundary_conds_khkm
1048
1049          ENDIF
1050
1051!
1052!--       If required, calculate radiative fluxes and heating rates
1053          IF ( radiation .AND. intermediate_timestep_count                     &
1054               == intermediate_timestep_count_max .AND. time_since_reference_point >    &
1055               skip_time_do_radiation )  THEN
1056
1057               time_radiation = time_radiation + dt_3d
1058
1059             IF ( time_radiation >= dt_radiation .OR. force_radiation_call )   &
1060             THEN
1061
1062                CALL cpu_log( log_point(50), 'radiation', 'start' )
1063
1064                IF ( .NOT. force_radiation_call )  THEN
1065                   time_radiation = time_radiation - dt_radiation
1066                ENDIF
1067
1068!
1069!--             Adjust the current_ time to the time step of the radiation model.
1070!--             Needed since radiation is pre-calculated and stored only on apparent
1071!--             solar positions
1072                it = FLOOR(time_since_reference_point/dt_radiation)
1073                tsrp_org = time_since_reference_point
1074                time_since_reference_point = REAL(it,wp) * dt_radiation
1075
1076                CALL radiation_control
1077
1078                CALL cpu_log( log_point(50), 'radiation', 'stop' )
1079
1080                IF ( urban_surface  .OR.  land_surface  .AND.                  &
1081                     radiation_interactions )  THEN
1082                   CALL cpu_log( log_point(75), 'radiation_interaction', 'start' )
1083                   CALL radiation_interaction
1084                   CALL cpu_log( log_point(75), 'radiation_interaction', 'stop' )
1085                ENDIF
1086   
1087!
1088!--             Return the current time to its original value
1089                time_since_reference_point = tsrp_org
1090
1091             ENDIF
1092          ENDIF
1093
1094       ENDDO   ! Intermediate step loop
1095!
1096!--    If required, consider chemical emissions
1097!--    (todo (FK): Implement hourly call of emissions, using time_utc from
1098!--                data_and_time_mod.f90;
1099!--                move the CALL to appropriate location)
1100       IF ( air_chemistry ) THEN
1101          CALL chem_emissions
1102       ENDIF
1103!
1104!--    If required, do UV exposure calculations
1105       IF ( uv_exposure )  THEN
1106          CALL uvem_calc_exposure
1107       ENDIF
1108!
1109!--    Increase simulation time and output times
1110       nr_timesteps_this_run      = nr_timesteps_this_run + 1
1111       current_timestep_number    = current_timestep_number + 1
1112       simulated_time             = simulated_time   + dt_3d
1113       time_since_reference_point = simulated_time - coupling_start_time
1114       simulated_time_chr         = time_to_string( time_since_reference_point )
1115
1116
1117
1118
1119       IF ( simulated_time >= skip_time_data_output_av )  THEN
1120          time_do_av         = time_do_av       + dt_3d
1121       ENDIF
1122       IF ( simulated_time >= skip_time_do2d_xy )  THEN
1123          time_do2d_xy       = time_do2d_xy     + dt_3d
1124       ENDIF
1125       IF ( simulated_time >= skip_time_do2d_xz )  THEN
1126          time_do2d_xz       = time_do2d_xz     + dt_3d
1127       ENDIF
1128       IF ( simulated_time >= skip_time_do2d_yz )  THEN
1129          time_do2d_yz       = time_do2d_yz     + dt_3d
1130       ENDIF
1131       IF ( simulated_time >= skip_time_do3d    )  THEN
1132          time_do3d          = time_do3d        + dt_3d
1133       ENDIF
1134       DO  mid = 1, masks
1135          IF ( simulated_time >= skip_time_domask(mid) )  THEN
1136             time_domask(mid)= time_domask(mid) + dt_3d
1137          ENDIF
1138       ENDDO
1139       time_dvrp          = time_dvrp        + dt_3d
1140       IF ( simulated_time >= skip_time_dosp )  THEN
1141          time_dosp       = time_dosp        + dt_3d
1142       ENDIF
1143       time_dots          = time_dots        + dt_3d
1144       IF ( .NOT. first_call_lpm )  THEN
1145          time_dopts      = time_dopts       + dt_3d
1146       ENDIF
1147       IF ( simulated_time >= skip_time_dopr )  THEN
1148          time_dopr       = time_dopr        + dt_3d
1149       ENDIF
1150       time_dopr_listing          = time_dopr_listing        + dt_3d
1151       time_run_control   = time_run_control + dt_3d
1152
1153!
1154!--    Data exchange between coupled models
1155       IF ( coupling_mode /= 'uncoupled'  .AND.  run_coupled                   &
1156                                          .AND. .NOT. vnested )  THEN
1157          time_coupling = time_coupling + dt_3d
1158
1159!
1160!--       In case of model termination initiated by the local model
1161!--       (terminate_coupled > 0), the coupler must be skipped because it would
1162!--       cause an MPI intercomminucation hang.
1163!--       If necessary, the coupler will be called at the beginning of the
1164!--       next restart run.
1165          DO WHILE ( time_coupling >= dt_coupling .AND. terminate_coupled == 0 )
1166             CALL surface_coupler
1167             time_coupling = time_coupling - dt_coupling
1168          ENDDO
1169       ENDIF
1170
1171!
1172!--    Execute the gust module actions
1173       IF ( gust_module_enabled )  THEN
1174          CALL gust_actions( 'after_integration' )
1175       ENDIF
1176
1177!
1178!--    Execute user-defined actions
1179       CALL user_actions( 'after_integration' )
1180
1181!
1182!--    If Galilei transformation is used, determine the distance that the
1183!--    model has moved so far
1184       IF ( galilei_transformation )  THEN
1185          advected_distance_x = advected_distance_x + u_gtrans * dt_3d
1186          advected_distance_y = advected_distance_y + v_gtrans * dt_3d
1187       ENDIF
1188
1189!
1190!--    Check, if restart is necessary (because cpu-time is expiring or
1191!--    because it is forced by user) and set stop flag
1192!--    This call is skipped if the remote model has already initiated a restart.
1193       IF ( .NOT. terminate_run )  CALL check_for_restart
1194
1195!
1196!--    Carry out statistical analysis and output at the requested output times.
1197!--    The MOD function is used for calculating the output time counters (like
1198!--    time_dopr) in order to regard a possible decrease of the output time
1199!--    interval in case of restart runs
1200
1201!
1202!--    Set a flag indicating that so far no statistics have been created
1203!--    for this time step
1204       flow_statistics_called = .FALSE.
1205
1206!
1207!--    If required, call flow_statistics for averaging in time
1208       IF ( averaging_interval_pr /= 0.0_wp  .AND.  &
1209            ( dt_dopr - time_dopr ) <= averaging_interval_pr  .AND.  &
1210            simulated_time >= skip_time_dopr )  THEN
1211          time_dopr_av = time_dopr_av + dt_3d
1212          IF ( time_dopr_av >= dt_averaging_input_pr )  THEN
1213             do_sum = .TRUE.
1214             time_dopr_av = MOD( time_dopr_av, &
1215                                    MAX( dt_averaging_input_pr, dt_3d ) )
1216          ENDIF
1217       ENDIF
1218       IF ( do_sum )  CALL flow_statistics
1219
1220!
1221!--    Sum-up 3d-arrays for later output of time-averaged 2d/3d/masked data
1222       IF ( averaging_interval /= 0.0_wp  .AND.                                &
1223            ( dt_data_output_av - time_do_av ) <= averaging_interval  .AND. &
1224            simulated_time >= skip_time_data_output_av )                    &
1225       THEN
1226          time_do_sla = time_do_sla + dt_3d
1227          IF ( time_do_sla >= dt_averaging_input )  THEN
1228             CALL sum_up_3d_data
1229             average_count_3d = average_count_3d + 1
1230             time_do_sla = MOD( time_do_sla, MAX( dt_averaging_input, dt_3d ) )
1231          ENDIF
1232       ENDIF
1233
1234!
1235!--    Calculate spectra for time averaging
1236       IF ( averaging_interval_sp /= 0.0_wp  .AND.  &
1237            ( dt_dosp - time_dosp ) <= averaging_interval_sp  .AND.  &
1238            simulated_time >= skip_time_dosp )  THEN
1239          time_dosp_av = time_dosp_av + dt_3d
1240          IF ( time_dosp_av >= dt_averaging_input_pr )  THEN
1241             CALL calc_spectra
1242             time_dosp_av = MOD( time_dosp_av, &
1243                                 MAX( dt_averaging_input_pr, dt_3d ) )
1244          ENDIF
1245       ENDIF
1246
1247!
1248!--    Call flight module and output data
1249       IF ( virtual_flight )  THEN
1250          CALL flight_measurement
1251          CALL data_output_flight
1252       ENDIF
1253
1254!
1255!--    Profile output (ASCII) on file
1256       IF ( time_dopr_listing >= dt_dopr_listing )  THEN
1257          CALL print_1d
1258          time_dopr_listing = MOD( time_dopr_listing, MAX( dt_dopr_listing, &
1259                                                           dt_3d ) )
1260       ENDIF
1261
1262!
1263!--    Graphic output for PROFIL
1264       IF ( time_dopr >= dt_dopr )  THEN
1265          IF ( dopr_n /= 0 )  CALL data_output_profiles
1266          time_dopr = MOD( time_dopr, MAX( dt_dopr, dt_3d ) )
1267          time_dopr_av = 0.0_wp    ! due to averaging (see above)
1268       ENDIF
1269
1270!
1271!--    Graphic output for time series
1272       IF ( time_dots >= dt_dots )  THEN
1273          CALL data_output_tseries
1274          time_dots = MOD( time_dots, MAX( dt_dots, dt_3d ) )
1275       ENDIF
1276
1277!
1278!--    Output of spectra (formatted for use with PROFIL), in case of no
1279!--    time averaging, spectra has to be calculated before
1280       IF ( time_dosp >= dt_dosp )  THEN
1281          IF ( average_count_sp == 0 )  CALL calc_spectra
1282          CALL data_output_spectra
1283          time_dosp = MOD( time_dosp, MAX( dt_dosp, dt_3d ) )
1284       ENDIF
1285
1286!
1287!--    2d-data output (cross-sections)
1288       IF ( time_do2d_xy >= dt_do2d_xy )  THEN
1289          CALL data_output_2d( 'xy', 0 )
1290          time_do2d_xy = MOD( time_do2d_xy, MAX( dt_do2d_xy, dt_3d ) )
1291       ENDIF
1292       IF ( time_do2d_xz >= dt_do2d_xz )  THEN
1293          CALL data_output_2d( 'xz', 0 )
1294          time_do2d_xz = MOD( time_do2d_xz, MAX( dt_do2d_xz, dt_3d ) )
1295       ENDIF
1296       IF ( time_do2d_yz >= dt_do2d_yz )  THEN
1297          CALL data_output_2d( 'yz', 0 )
1298          time_do2d_yz = MOD( time_do2d_yz, MAX( dt_do2d_yz, dt_3d ) )
1299       ENDIF
1300
1301!
1302!--    3d-data output (volume data)
1303       IF ( time_do3d >= dt_do3d )  THEN
1304          CALL data_output_3d( 0 )
1305          time_do3d = MOD( time_do3d, MAX( dt_do3d, dt_3d ) )
1306       ENDIF
1307
1308!
1309!--    Masked data output
1310       DO  mid = 1, masks
1311          IF ( time_domask(mid) >= dt_domask(mid) )  THEN
1312             CALL data_output_mask( 0 )
1313             time_domask(mid) = MOD( time_domask(mid),  &
1314                                     MAX( dt_domask(mid), dt_3d ) )
1315          ENDIF
1316       ENDDO
1317
1318!
1319!--    Output of time-averaged 2d/3d/masked data
1320       IF ( time_do_av >= dt_data_output_av )  THEN
1321          CALL average_3d_data
1322          CALL data_output_2d( 'xy', 1 )
1323          CALL data_output_2d( 'xz', 1 )
1324          CALL data_output_2d( 'yz', 1 )
1325          CALL data_output_3d( 1 )
1326          DO  mid = 1, masks
1327             CALL data_output_mask( 1 )
1328          ENDDO
1329          time_do_av = MOD( time_do_av, MAX( dt_data_output_av, dt_3d ) )
1330       ENDIF
1331
1332!
1333!--    Output of particle time series
1334       IF ( particle_advection )  THEN
1335          IF ( time_dopts >= dt_dopts  .OR. &
1336               ( simulated_time >= particle_advection_start  .AND. &
1337                 first_call_lpm ) )  THEN
1338             CALL data_output_ptseries
1339             time_dopts = MOD( time_dopts, MAX( dt_dopts, dt_3d ) )
1340          ENDIF
1341       ENDIF
1342
1343!
1344!--    Output of dvrp-graphics (isosurface, particles, slicer)
1345#if defined( __dvrp_graphics )
1346       CALL DVRP_LOG_EVENT( -2, current_timestep_number-1 )
1347#endif
1348       IF ( time_dvrp >= dt_dvrp )  THEN
1349          CALL data_output_dvrp
1350          time_dvrp = MOD( time_dvrp, MAX( dt_dvrp, dt_3d ) )
1351       ENDIF
1352#if defined( __dvrp_graphics )
1353       CALL DVRP_LOG_EVENT( 2, current_timestep_number )
1354#endif
1355
1356!
1357!--    If required, set the heat flux for the next time step at a random value
1358       IF ( constant_heatflux  .AND.  random_heatflux )  THEN
1359          IF ( surf_def_h(0)%ns >= 1 )  CALL disturb_heatflux( surf_def_h(0) )
1360          IF ( surf_lsm_h%ns    >= 1 )  CALL disturb_heatflux( surf_lsm_h    )
1361          IF ( surf_usm_h%ns    >= 1 )  CALL disturb_heatflux( surf_usm_h    )
1362       ENDIF
1363
1364!
1365!--    Execute the gust module actions
1366       IF ( gust_module_enabled )  THEN
1367          CALL gust_actions( 'after_timestep' )
1368       ENDIF
1369
1370!
1371!--    Execute user-defined actions
1372       CALL user_actions( 'after_timestep' )
1373
1374!
1375!--    Determine size of next time step. Save timestep dt_3d because it is
1376!--    newly calculated in routine timestep, but required further below for
1377!--    steering the run control output interval
1378       dt_3d_old = dt_3d
1379       CALL timestep
1380
1381!
1382!--    Synchronize the timestep in case of nested run.
1383       IF ( nested_run )  THEN
1384!
1385!--       Synchronize by unifying the time step.
1386!--       Global minimum of all time-steps is used for all.
1387          CALL pmci_synchronize
1388       ENDIF
1389
1390!
1391!--    Computation and output of run control parameters.
1392!--    This is also done whenever perturbations have been imposed
1393       IF ( time_run_control >= dt_run_control  .OR.                     &
1394            timestep_scheme(1:5) /= 'runge'  .OR.  disturbance_created ) &
1395       THEN
1396          CALL run_control
1397          IF ( time_run_control >= dt_run_control )  THEN
1398             time_run_control = MOD( time_run_control, &
1399                                     MAX( dt_run_control, dt_3d_old ) )
1400          ENDIF
1401       ENDIF
1402
1403!
1404!--    Output elapsed simulated time in form of a progress bar on stdout
1405       IF ( myid == 0 )  CALL output_progress_bar
1406
1407       CALL cpu_log( log_point_s(10), 'timesteps', 'stop' )
1408
1409
1410    ENDDO   ! time loop
1411
1412!-- Vertical nesting: Deallocate variables initialized for vertical nesting   
1413    IF ( vnest_init )  CALL vnest_deallocate
1414
1415    IF ( myid == 0 )  CALL finish_progress_bar
1416
1417#if defined( __dvrp_graphics )
1418    CALL DVRP_LOG_EVENT( -2, current_timestep_number )
1419#endif
1420
1421    CALL location_message( 'finished time-stepping', .TRUE. )
1422
1423 END SUBROUTINE time_integration
Note: See TracBrowser for help on using the repository browser.