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

Last change on this file since 3294 was 3294, checked in by raasch, 6 years ago

modularization of the ocean code

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