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

Last change on this file since 1276 was 1276, checked in by heinze, 11 years ago

Usage of Dirichlet bottom boundary condition for scalars in conjunction with large scale forcing enabled

  • Property svn:keywords set to Id
File size: 32.3 KB
Line 
1 SUBROUTINE time_integration
2
3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later 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-2012  Leibniz University Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! ------------------
22! Use LSF_DATA also in case of Dirichlet bottom boundary condition for scalars
23!
24! Former revisions:
25! -----------------
26! $Id: time_integration.f90 1276 2014-01-15 13:40:41Z heinze $
27!
28! 1257 2013-11-08 15:18:40Z raasch
29! acc-update-host directive for timestep removed
30!
31! 1241 2013-10-30 11:36:58Z heinze
32! Generalize calc_mean_profile for wider use
33! Determine shf and qsws in dependence on data from LSF_DATA
34! Determine ug and vg in dependence on data from LSF_DATA
35! 1221 2013-09-10 08:59:13Z raasch
36! host update of arrays before timestep is called
37!
38! 1179 2013-06-14 05:57:58Z raasch
39! mean profiles for reference state are only calculated if required,
40! small bugfix for background communication
41!
42! 1171 2013-05-30 11:27:45Z raasch
43! split of prognostic_equations deactivated (comment lines), for the time being
44!
45! 1128 2013-04-12 06:19:32Z raasch
46! asynchronous transfer of ghost point data realized for acc-optimized version:
47! prognostic_equations are first called two times for those points required for
48! the left-right and north-south exchange, respectively, and then for the
49! remaining points,
50! those parts requiring global communication moved from prognostic_equations to
51! here
52!
53! 1115 2013-03-26 18:16:16Z hoffmann
54! calculation of qr and nr is restricted to precipitation
55!
56! 1113 2013-03-10 02:48:14Z raasch
57! GPU-porting of boundary conditions,
58! openACC directives updated
59! formal parameter removed from routine boundary_conds
60!
61! 1111 2013-03-08 23:54:10Z raasch
62! +internal timestep counter for cpu statistics added,
63! openACC directives updated
64!
65! 1092 2013-02-02 11:24:22Z raasch
66! unused variables removed
67!
68! 1065 2012-11-22 17:42:36Z hoffmann
69! exchange of diss (dissipation rate) in case of turbulence = .TRUE. added
70!
71! 1053 2012-11-13 17:11:03Z hoffmann
72! exchange of ghost points for nr, qr added
73!
74! 1036 2012-10-22 13:43:42Z raasch
75! code put under GPL (PALM 3.9)
76!
77! 1019 2012-09-28 06:46:45Z raasch
78! non-optimized version of prognostic_equations removed
79!
80! 1015 2012-09-27 09:23:24Z raasch
81! +call of prognostic_equations_acc
82!
83! 1001 2012-09-13 14:08:46Z raasch
84! all actions concerning leapfrog- and upstream-spline-scheme removed
85!
86! 849 2012-03-15 10:35:09Z raasch
87! advec_particles renamed lpm, first_call_advec_particles renamed first_call_lpm
88!
89! 825 2012-02-19 03:03:44Z raasch
90! wang_collision_kernel renamed wang_kernel
91!
92! 790 2011-11-29 03:11:20Z raasch
93! exchange of ghostpoints for array diss
94!
95! 707 2011-03-29 11:39:40Z raasch
96! bc_lr/ns replaced by bc_lr/ns_cyc, calls of exchange_horiz are modified,
97! adaption to sloping surface
98!
99! 667  2010-12-23 12:06:00Z suehring/gryschka
100! Calls of exchange_horiz are modified.
101! Adaption to slooping surface.
102!
103! 449 2010-02-02 11:23:59Z raasch
104! Bugfix: exchange of ghost points for prho included
105!
106! 410 2009-12-04 17:05:40Z letzel
107! masked data output
108!
109! 388 2009-09-23 09:40:33Z raasch
110! Using prho instead of rho in diffusvities.
111! Coupling with independent precursor runs.
112! Bugfix: output of particle time series only if particle advection is switched
113!         on
114!
115! 151 2008-03-07 13:42:18Z raasch
116! inflow turbulence is imposed by calling new routine inflow_turbulence
117!
118! 108 2007-08-24 15:10:38Z letzel
119! Call of new routine surface_coupler,
120! presure solver is called after the first Runge-Kutta substep instead of the
121! last in case that call_psolver_at_all_substeps = .F.; for this case, the
122! random perturbation has to be added to the velocity fields also after the
123! first substep
124!
125! 97 2007-06-21 08:23:15Z raasch
126! diffusivities is called with argument rho in case of ocean runs,
127! new argument pt_/prho_reference in calls of diffusivities,
128! ghostpoint exchange for salinity and density
129!
130! 87 2007-05-22 15:46:47Z raasch
131! var_hom renamed pr_palm
132!
133! 75 2007-03-22 09:54:05Z raasch
134! Move call of user_actions( 'after_integration' ) below increment of times
135! and counters,
136! calls of prognostic_equations_.. changed to .._noopt, .._cache, and
137! .._vector, these calls are now controlled by switch loop_optimization,
138! uxrp, vynp eliminated, 2nd+3rd argument removed from exchange horiz,
139! moisture renamed humidity
140!
141! RCS Log replace by Id keyword, revision history cleaned up
142!
143! Revision 1.8  2006/08/22 14:16:05  raasch
144! Disturbances are imposed only for the last Runge-Kutta-substep
145!
146! Revision 1.2  2004/04/30 13:03:40  raasch
147! decalpha-specific warning removed, routine name changed to time_integration,
148! particle advection is carried out only once during the intermediate steps,
149! impulse_advec renamed momentum_advec
150!
151! Revision 1.1  1997/08/11 06:19:04  raasch
152! Initial revision
153!
154!
155! Description:
156! ------------
157! Integration in time of the model equations, statistical analysis and graphic
158! output
159!------------------------------------------------------------------------------!
160
161    USE advec_ws
162    USE arrays_3d
163    USE averaging
164    USE buoyancy_mod
165    USE control_parameters
166    USE cpulog
167#if defined( __dvrp_graphics )
168    USE DVRP
169#endif
170    USE grid_variables
171    USE indices
172    USE interaction_droplets_ptq_mod
173    USE interfaces
174    USE ls_forcing_mod
175    USE particle_attributes
176    USE pegrid
177    USE production_e_mod
178    USE prognostic_equations_mod
179    USE statistics
180    USE user_actions_mod
181
182    IMPLICIT NONE
183
184    CHARACTER (LEN=9) ::  time_to_string
185
186!
187!-- At the beginning of a simulation determine the time step as well as
188!-- determine and print out the run control parameters
189    IF ( simulated_time == 0.0 )  CALL timestep
190
191    CALL run_control
192
193
194!
195!-- Data exchange between coupled models in case that a call has been omitted
196!-- at the end of the previous run of a job chain.
197    IF ( coupling_mode /= 'uncoupled'  .AND.  run_coupled )  THEN
198!
199!--    In case of model termination initiated by the local model the coupler
200!--    must not be called because this would again cause an MPI hang.
201       DO WHILE ( time_coupling >= dt_coupling .AND. terminate_coupled == 0 )
202          CALL surface_coupler
203          time_coupling = time_coupling - dt_coupling
204       ENDDO
205       IF (time_coupling == 0.0 .AND. time_since_reference_point < dt_coupling)&
206       THEN
207          time_coupling = time_since_reference_point
208       ENDIF
209    ENDIF
210
211
212#if defined( __dvrp_graphics )
213!
214!-- Time measurement with dvrp software 
215    CALL DVRP_LOG_EVENT( 2, current_timestep_number )
216#endif
217
218!
219!-- Start of the time loop
220    DO  WHILE ( simulated_time < end_time  .AND.  .NOT. stop_dt  .AND. &
221                .NOT. terminate_run )
222
223       CALL cpu_log( log_point_s(10), 'timesteps', 'start' )
224
225!
226!--    Determine size of next time step
227       IF ( simulated_time /= 0.0 )  THEN
228          CALL timestep
229       ENDIF
230
231!
232!--    Determine ug, vg and w_subs in dependence on data from external file
233!--    LSF_DATA
234       IF ( large_scale_forcing .AND. lsf_vert ) THEN
235           CALL ls_forcing_vert ( simulated_time )
236       ENDIF
237
238!
239!--    Execute the user-defined actions
240       CALL user_actions( 'before_timestep' )
241
242!
243!--    Start of intermediate step loop
244       intermediate_timestep_count = 0
245       DO  WHILE ( intermediate_timestep_count < &
246                   intermediate_timestep_count_max )
247
248          intermediate_timestep_count = intermediate_timestep_count + 1
249
250!
251!--       Set the steering factors for the prognostic equations which depend
252!--       on the timestep scheme
253          CALL timestep_scheme_steering
254
255!
256!--       Calculate those variables needed in the tendency terms which need
257!--       global communication
258          IF ( .NOT. use_single_reference_value  .AND. &
259               .NOT. use_initial_profile_as_reference )  THEN
260!
261!--          Horizontally averaged profiles to be used as reference state in
262!--          buoyancy terms (WARNING: only the respective last call of
263!--          calc_mean_profile defines the reference state!)
264             IF ( .NOT. neutral )  CALL calc_mean_profile( pt, 4, 'time_int' )
265             IF ( ocean         )  CALL calc_mean_profile( rho, 64, 'time_int' )
266             IF ( humidity      )  CALL calc_mean_profile( vpt, 44, 'time_int' )
267          ENDIF
268
269          IF ( .NOT. constant_diffusion )  CALL production_e_init
270          IF ( ( ws_scheme_mom .OR. ws_scheme_sca )  .AND.  &
271               intermediate_timestep_count == 1 )  CALL ws_statistics
272
273!
274!--       Solve the prognostic equations. A fast cache optimized version with
275!--       only one single loop is used in case of Piascek-Williams advection
276!--       scheme. NEC vector machines use a different version, because
277!--       in the other versions a good vectorization is prohibited due to
278!--       inlining problems.
279          IF ( loop_optimization == 'cache' )  THEN
280             CALL prognostic_equations_cache
281          ELSEIF ( loop_optimization == 'vector' )  THEN
282             CALL prognostic_equations_vector
283          ELSEIF ( loop_optimization == 'acc' )  THEN
284             i_left  = nxl;         i_right = nxr
285             j_south = nys;         j_north = nyn
286             CALL prognostic_equations_acc
287
288!             i_left  = nxl;         i_right = nxl+nbgp-1
289!             j_south = nys;         j_north = nyn
290!             CALL prognostic_equations_acc
291!             i_left  = nxr-nbgp+1;  i_right = nxr
292!             j_south = nys;         j_north = nyn
293!             CALL prognostic_equations_acc
294
295!
296!--          Exchange of ghost points (lateral boundary conditions)
297             IF ( background_communication )  THEN
298
299                CALL cpu_log( log_point(26), 'exchange-horiz-progn', 'start' )
300               
301                send_receive = 'lr'
302                sendrecv_in_background = .TRUE.
303                req          = 0
304                req_count    = 0
305
306                IF ( numprocs == 1 )  THEN    ! workaround for single-core GPU runs
307                   on_device = .TRUE.         ! to be removed after complete porting
308                ELSE                          ! of ghost point exchange
309                   !$acc update host( e_p, pt_p, u_p, v_p, w_p )
310                ENDIF
311
312                CALL exchange_horiz( u_p, nbgp )
313                CALL exchange_horiz( v_p, nbgp )
314                CALL exchange_horiz( w_p, nbgp )
315                CALL exchange_horiz( pt_p, nbgp )
316                IF ( .NOT. constant_diffusion )  CALL exchange_horiz( e_p, nbgp )
317                IF ( ocean )  THEN
318                   CALL exchange_horiz( sa_p, nbgp )
319                   CALL exchange_horiz( rho, nbgp )
320                  CALL exchange_horiz( prho, nbgp )
321                ENDIF
322                IF (humidity  .OR.  passive_scalar)  THEN
323                   CALL exchange_horiz( q_p, nbgp )
324                   IF ( cloud_physics .AND. icloud_scheme == 0 )  THEN
325                      CALL exchange_horiz( qr_p, nbgp )
326                      CALL exchange_horiz( nr_p, nbgp )
327                   ENDIF
328                ENDIF
329                IF ( cloud_droplets )  THEN
330                   CALL exchange_horiz( ql, nbgp )
331                   CALL exchange_horiz( ql_c, nbgp )
332                   CALL exchange_horiz( ql_v, nbgp )
333                   CALL exchange_horiz( ql_vp, nbgp )
334                ENDIF
335                IF ( wang_kernel  .OR.  turbulence )  CALL exchange_horiz( diss, nbgp )
336
337                IF ( numprocs == 1 )  THEN    ! workaround for single-core GPU runs
338                   on_device = .FALSE.        ! to be removed after complete porting
339                ELSE                          ! of ghost point exchange
340                   !$acc update device( e_p, pt_p, u_p, v_p, w_p )
341                ENDIF
342
343                sendrecv_in_background = .FALSE.
344
345                CALL cpu_log( log_point(26), 'exchange-horiz-progn', 'pause' )
346
347             ENDIF
348
349!             i_left  = nxl+nbgp;    i_right = nxr-nbgp
350!             j_south = nys;         j_north = nys+nbgp-1
351!             CALL prognostic_equations_acc
352!             i_left  = nxl+nbgp;    i_right = nxr-nbgp
353!             j_south = nyn-nbgp+1;  j_north = nyn
354!             CALL prognostic_equations_acc
355
356             IF ( background_communication )  THEN
357                CALL cpu_log( log_point(41), 'exchange-horiz-wait', 'start' )
358#if defined( __parallel )
359                CALL MPI_WAITALL( req_count, req, wait_stat, ierr )
360#endif
361                CALL cpu_log( log_point(41), 'exchange-horiz-wait', 'pause' )
362
363                CALL cpu_log( log_point(26), 'exchange-horiz-progn', 'continue' )
364
365                send_receive = 'ns'
366                sendrecv_in_background = .TRUE.
367                req          = 0
368                req_count    = 0
369
370                IF ( numprocs == 1 )  THEN    ! workaround for single-core GPU runs
371                   on_device = .TRUE.         ! to be removed after complete porting
372                ELSE                          ! of ghost point exchange
373                   !$acc update host( e_p, pt_p, u_p, v_p, w_p )
374                ENDIF
375
376                CALL exchange_horiz( u_p, nbgp )
377                CALL exchange_horiz( v_p, nbgp )
378                CALL exchange_horiz( w_p, nbgp )
379                CALL exchange_horiz( pt_p, nbgp )
380                IF ( .NOT. constant_diffusion )  CALL exchange_horiz( e_p, nbgp )
381                IF ( ocean )  THEN
382                   CALL exchange_horiz( sa_p, nbgp )
383                   CALL exchange_horiz( rho, nbgp )
384                  CALL exchange_horiz( prho, nbgp )
385                ENDIF
386                IF (humidity  .OR.  passive_scalar)  THEN
387                   CALL exchange_horiz( q_p, nbgp )
388                   IF ( cloud_physics .AND. icloud_scheme == 0 )  THEN
389                      CALL exchange_horiz( qr_p, nbgp )
390                      CALL exchange_horiz( nr_p, nbgp )
391                   ENDIF
392                ENDIF
393                IF ( cloud_droplets )  THEN
394                   CALL exchange_horiz( ql, nbgp )
395                   CALL exchange_horiz( ql_c, nbgp )
396                   CALL exchange_horiz( ql_v, nbgp )
397                   CALL exchange_horiz( ql_vp, nbgp )
398                ENDIF
399                IF ( wang_kernel  .OR.  turbulence )  CALL exchange_horiz( diss, nbgp )
400
401                IF ( numprocs == 1 )  THEN    ! workaround for single-core GPU runs
402                   on_device = .FALSE.        ! to be removed after complete porting
403                ELSE                          ! of ghost point exchange
404                   !$acc update device( e_p, pt_p, u_p, v_p, w_p )
405                ENDIF
406
407                sendrecv_in_background = .FALSE.
408
409                CALL cpu_log( log_point(26), 'exchange-horiz-progn', 'stop' )
410
411             ENDIF
412
413!             i_left  = nxl+nbgp;    i_right = nxr-nbgp
414!             j_south = nys+nbgp;    j_north = nyn-nbgp
415!             CALL prognostic_equations_acc
416
417             IF ( background_communication )  THEN
418                CALL cpu_log( log_point(41), 'exchange-horiz-wait', 'continue' )
419#if defined( __parallel )
420                CALL MPI_WAITALL( req_count, req, wait_stat, ierr )
421#endif
422                send_receive = 'al'
423                CALL cpu_log( log_point(41), 'exchange-horiz-wait', 'stop' )
424             ENDIF
425
426          ENDIF
427
428!
429!--       Particle transport/physics with the Lagrangian particle model
430!--       (only once during intermediate steps, because it uses an Euler-step)
431!--       ### particle model should be moved before prognostic_equations, in order
432!--       to regard droplet interactions directly
433          IF ( particle_advection  .AND.                         &
434               simulated_time >= particle_advection_start  .AND. &
435               intermediate_timestep_count == 1 )  THEN
436             CALL lpm
437             first_call_lpm = .FALSE.
438          ENDIF
439
440!
441!--       Interaction of droplets with temperature and specific humidity.
442!--       Droplet condensation and evaporation is calculated within
443!--       advec_particles.
444          IF ( cloud_droplets  .AND.  &
445               intermediate_timestep_count == intermediate_timestep_count_max )&
446          THEN
447             CALL interaction_droplets_ptq
448          ENDIF
449
450!
451!--       Exchange of ghost points (lateral boundary conditions)
452          IF ( .NOT. background_communication )  THEN
453
454             CALL cpu_log( log_point(26), 'exchange-horiz-progn', 'start' )
455
456             IF ( numprocs == 1 )  THEN    ! workaround for single-core GPU runs
457                on_device = .TRUE.         ! to be removed after complete porting
458             ELSE                          ! of ghost point exchange
459                !$acc update host( e_p, pt_p, u_p, v_p, w_p )
460             ENDIF
461
462             CALL exchange_horiz( u_p, nbgp )
463             CALL exchange_horiz( v_p, nbgp )
464             CALL exchange_horiz( w_p, nbgp )
465             CALL exchange_horiz( pt_p, nbgp )
466             IF ( .NOT. constant_diffusion )  CALL exchange_horiz( e_p, nbgp )
467             IF ( ocean )  THEN
468                CALL exchange_horiz( sa_p, nbgp )
469                CALL exchange_horiz( rho, nbgp )
470                CALL exchange_horiz( prho, nbgp )
471             ENDIF
472             IF (humidity  .OR.  passive_scalar)  THEN
473                CALL exchange_horiz( q_p, nbgp )
474                IF ( cloud_physics .AND. icloud_scheme == 0  .AND.  &
475                     precipitation )  THEN
476                   CALL exchange_horiz( qr_p, nbgp )
477                   CALL exchange_horiz( nr_p, nbgp )
478                ENDIF
479             ENDIF
480             IF ( cloud_droplets )  THEN
481                CALL exchange_horiz( ql, nbgp )
482                CALL exchange_horiz( ql_c, nbgp )
483                CALL exchange_horiz( ql_v, nbgp )
484                CALL exchange_horiz( ql_vp, nbgp )
485             ENDIF
486             IF ( wang_kernel  .OR.  turbulence )  CALL exchange_horiz( diss, nbgp )
487
488             IF ( numprocs == 1 )  THEN    ! workaround for single-core GPU runs
489                on_device = .FALSE.        ! to be removed after complete porting
490             ELSE                          ! of ghost point exchange
491                !$acc update device( e_p, pt_p, u_p, v_p, w_p )
492             ENDIF
493
494             CALL cpu_log( log_point(26), 'exchange-horiz-progn', 'stop' )
495
496          ENDIF
497
498!
499!--       Boundary conditions for the prognostic quantities (except of the
500!--       velocities at the outflow in case of a non-cyclic lateral wall)
501          CALL boundary_conds
502
503!
504!--       Swap the time levels in preparation for the next time step.
505          CALL swap_timelevel
506
507!
508!--       Temperature offset must be imposed at cyclic boundaries in x-direction
509!--       when a sloping surface is used
510          IF ( sloping_surface )  THEN
511             IF ( nxl ==  0 )  pt(:,:,nxlg:nxl-1) = pt(:,:,nxlg:nxl-1) - &
512                                                    pt_slope_offset
513             IF ( nxr == nx )  pt(:,:,nxr+1:nxrg) = pt(:,:,nxr+1:nxrg) + &
514                                                    pt_slope_offset
515          ENDIF
516
517!
518!--       Impose a turbulent inflow using the recycling method
519          IF ( turbulent_inflow )  CALL  inflow_turbulence
520
521!
522!--       Impose a random perturbation on the horizontal velocity field
523          IF ( create_disturbances  .AND.                                      &
524               ( call_psolver_at_all_substeps  .AND.                           &
525               intermediate_timestep_count == intermediate_timestep_count_max )&
526          .OR. ( .NOT. call_psolver_at_all_substeps  .AND.                     &
527               intermediate_timestep_count == 1 ) )                            &
528          THEN
529             time_disturb = time_disturb + dt_3d
530             IF ( time_disturb >= dt_disturb )  THEN
531                !$acc update host( u, v )
532                IF ( numprocs == 1 )  on_device = .FALSE.  ! workaround, remove later
533                IF ( hom(nzb+5,1,pr_palm,0) < disturbance_energy_limit )  THEN
534                   CALL disturb_field( nzb_u_inner, tend, u )
535                   CALL disturb_field( nzb_v_inner, tend, v )
536                ELSEIF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
537!
538!--                Runs with a non-cyclic lateral wall need perturbations
539!--                near the inflow throughout the whole simulation
540                   dist_range = 1
541                   CALL disturb_field( nzb_u_inner, tend, u )
542                   CALL disturb_field( nzb_v_inner, tend, v )
543                   dist_range = 0
544                ENDIF
545                IF ( numprocs == 1 )  on_device = .TRUE.  ! workaround, remove later
546                !$acc update device( u, v )
547                time_disturb = time_disturb - dt_disturb
548             ENDIF
549          ENDIF
550
551!
552!--       Reduce the velocity divergence via the equation for perturbation
553!--       pressure.
554          IF ( intermediate_timestep_count == 1  .OR. &
555                call_psolver_at_all_substeps )  THEN
556             CALL pres
557          ENDIF
558
559!
560!--       If required, compute liquid water content
561          IF ( cloud_physics )  THEN
562             CALL calc_liquid_water_content
563             !$acc update device( ql )
564          ENDIF
565!
566!--       If required, compute virtual potential temperature
567          IF ( humidity )  THEN
568             CALL compute_vpt 
569             !$acc update device( vpt )
570          ENDIF 
571!
572!--       Compute the diffusion quantities
573          IF ( .NOT. constant_diffusion )  THEN
574
575!
576!--          Determine surface fluxes shf and qsws and surface values
577!--          pt_surface and q_surface in dependence on data from external
578!--          file LSF_DATA respectively
579             IF ( ( large_scale_forcing .AND. lsf_surf ) .AND. &
580                 intermediate_timestep_count == intermediate_timestep_count_max )&
581             THEN
582                CALL ls_forcing_surf ( simulated_time )
583             ENDIF
584
585!
586!--          First the vertical fluxes in the Prandtl layer are being computed
587             IF ( prandtl_layer )  THEN
588                CALL cpu_log( log_point(19), 'prandtl_fluxes', 'start' )
589                CALL prandtl_fluxes
590                CALL cpu_log( log_point(19), 'prandtl_fluxes', 'stop' )
591             ENDIF
592
593!
594!--          Compute the diffusion coefficients
595             CALL cpu_log( log_point(17), 'diffusivities', 'start' )
596             IF ( .NOT. humidity ) THEN
597                IF ( ocean )  THEN
598                   CALL diffusivities( prho, prho_reference )
599                ELSE
600                   CALL diffusivities( pt, pt_reference )
601                ENDIF
602             ELSE
603                CALL diffusivities( vpt, pt_reference )
604             ENDIF
605             CALL cpu_log( log_point(17), 'diffusivities', 'stop' )
606
607          ENDIF
608
609       ENDDO   ! Intermediate step loop
610
611!
612!--    Increase simulation time and output times
613       nr_timesteps_this_run      = nr_timesteps_this_run + 1
614       current_timestep_number    = current_timestep_number + 1
615       simulated_time             = simulated_time   + dt_3d
616       simulated_time_chr         = time_to_string( simulated_time )
617       time_since_reference_point = simulated_time - coupling_start_time
618
619       IF ( simulated_time >= skip_time_data_output_av )  THEN
620          time_do_av         = time_do_av       + dt_3d
621       ENDIF
622       IF ( simulated_time >= skip_time_do2d_xy )  THEN
623          time_do2d_xy       = time_do2d_xy     + dt_3d
624       ENDIF
625       IF ( simulated_time >= skip_time_do2d_xz )  THEN
626          time_do2d_xz       = time_do2d_xz     + dt_3d
627       ENDIF
628       IF ( simulated_time >= skip_time_do2d_yz )  THEN
629          time_do2d_yz       = time_do2d_yz     + dt_3d
630       ENDIF
631       IF ( simulated_time >= skip_time_do3d    )  THEN
632          time_do3d          = time_do3d        + dt_3d
633       ENDIF
634       DO  mid = 1, masks
635          IF ( simulated_time >= skip_time_domask(mid) )  THEN
636             time_domask(mid)= time_domask(mid) + dt_3d
637          ENDIF
638       ENDDO
639       time_dvrp          = time_dvrp        + dt_3d
640       IF ( simulated_time >= skip_time_dosp )  THEN
641          time_dosp       = time_dosp        + dt_3d
642       ENDIF
643       time_dots          = time_dots        + dt_3d
644       IF ( .NOT. first_call_lpm )  THEN
645          time_dopts      = time_dopts       + dt_3d
646       ENDIF
647       IF ( simulated_time >= skip_time_dopr )  THEN
648          time_dopr       = time_dopr        + dt_3d
649       ENDIF
650       time_dopr_listing          = time_dopr_listing        + dt_3d
651       time_run_control   = time_run_control + dt_3d
652
653!
654!--    Data exchange between coupled models
655       IF ( coupling_mode /= 'uncoupled'  .AND.  run_coupled )  THEN
656          time_coupling = time_coupling + dt_3d
657
658!
659!--       In case of model termination initiated by the local model
660!--       (terminate_coupled > 0), the coupler must be skipped because it would
661!--       cause an MPI intercomminucation hang.
662!--       If necessary, the coupler will be called at the beginning of the
663!--       next restart run.
664          DO WHILE ( time_coupling >= dt_coupling .AND. terminate_coupled == 0 )
665             CALL surface_coupler
666             time_coupling = time_coupling - dt_coupling
667          ENDDO
668       ENDIF
669
670!
671!--    Execute user-defined actions
672       CALL user_actions( 'after_integration' )
673
674!
675!--    If Galilei transformation is used, determine the distance that the
676!--    model has moved so far
677       IF ( galilei_transformation )  THEN
678          advected_distance_x = advected_distance_x + u_gtrans * dt_3d
679          advected_distance_y = advected_distance_y + v_gtrans * dt_3d
680       ENDIF
681
682!
683!--    Check, if restart is necessary (because cpu-time is expiring or
684!--    because it is forced by user) and set stop flag
685!--    This call is skipped if the remote model has already initiated a restart.
686       IF ( .NOT. terminate_run )  CALL check_for_restart
687
688!
689!--    Carry out statistical analysis and output at the requested output times.
690!--    The MOD function is used for calculating the output time counters (like
691!--    time_dopr) in order to regard a possible decrease of the output time
692!--    interval in case of restart runs
693
694!
695!--    Set a flag indicating that so far no statistics have been created
696!--    for this time step
697       flow_statistics_called = .FALSE.
698
699!
700!--    If required, call flow_statistics for averaging in time
701       IF ( averaging_interval_pr /= 0.0  .AND.  &
702            ( dt_dopr - time_dopr ) <= averaging_interval_pr  .AND.  &
703            simulated_time >= skip_time_dopr )  THEN
704          time_dopr_av = time_dopr_av + dt_3d
705          IF ( time_dopr_av >= dt_averaging_input_pr )  THEN
706             do_sum = .TRUE.
707             time_dopr_av = MOD( time_dopr_av, &
708                                    MAX( dt_averaging_input_pr, dt_3d ) )
709          ENDIF
710       ENDIF
711       IF ( do_sum )  CALL flow_statistics
712
713!
714!--    Sum-up 3d-arrays for later output of time-averaged 2d/3d/masked data
715       IF ( averaging_interval /= 0.0  .AND.                                &
716            ( dt_data_output_av - time_do_av ) <= averaging_interval  .AND. &
717            simulated_time >= skip_time_data_output_av )                    &
718       THEN
719          time_do_sla = time_do_sla + dt_3d
720          IF ( time_do_sla >= dt_averaging_input )  THEN
721             CALL sum_up_3d_data
722             average_count_3d = average_count_3d + 1
723             time_do_sla = MOD( time_do_sla, MAX( dt_averaging_input, dt_3d ) )
724          ENDIF
725       ENDIF
726
727!
728!--    Calculate spectra for time averaging
729       IF ( averaging_interval_sp /= 0.0  .AND.  &
730            ( dt_dosp - time_dosp ) <= averaging_interval_sp  .AND.  &
731            simulated_time >= skip_time_dosp )  THEN
732          time_dosp_av = time_dosp_av + dt_3d
733          IF ( time_dosp_av >= dt_averaging_input_pr )  THEN
734             CALL calc_spectra
735             time_dosp_av = MOD( time_dosp_av, &
736                                 MAX( dt_averaging_input_pr, dt_3d ) )
737          ENDIF
738       ENDIF
739
740!
741!--    Computation and output of run control parameters.
742!--    This is also done whenever perturbations have been imposed
743       IF ( time_run_control >= dt_run_control  .OR.                     &
744            timestep_scheme(1:5) /= 'runge'  .OR.  disturbance_created ) &
745       THEN
746          CALL run_control
747          IF ( time_run_control >= dt_run_control )  THEN
748             time_run_control = MOD( time_run_control, &
749                                     MAX( dt_run_control, dt_3d ) )
750          ENDIF
751       ENDIF
752
753!
754!--    Profile output (ASCII) on file
755       IF ( time_dopr_listing >= dt_dopr_listing )  THEN
756          CALL print_1d
757          time_dopr_listing = MOD( time_dopr_listing, MAX( dt_dopr_listing, &
758                                                           dt_3d ) )
759       ENDIF
760
761!
762!--    Graphic output for PROFIL
763       IF ( time_dopr >= dt_dopr )  THEN
764          IF ( dopr_n /= 0 )  CALL data_output_profiles
765          time_dopr = MOD( time_dopr, MAX( dt_dopr, dt_3d ) )
766          time_dopr_av = 0.0    ! due to averaging (see above)
767       ENDIF
768
769!
770!--    Graphic output for time series
771       IF ( time_dots >= dt_dots )  THEN
772          CALL data_output_tseries
773          time_dots = MOD( time_dots, MAX( dt_dots, dt_3d ) )
774       ENDIF
775
776!
777!--    Output of spectra (formatted for use with PROFIL), in case of no
778!--    time averaging, spectra has to be calculated before
779       IF ( time_dosp >= dt_dosp )  THEN
780          IF ( average_count_sp == 0 )  CALL calc_spectra
781          CALL data_output_spectra
782          time_dosp = MOD( time_dosp, MAX( dt_dosp, dt_3d ) )
783       ENDIF
784
785!
786!--    2d-data output (cross-sections)
787       IF ( time_do2d_xy >= dt_do2d_xy )  THEN
788          CALL data_output_2d( 'xy', 0 )
789          time_do2d_xy = MOD( time_do2d_xy, MAX( dt_do2d_xy, dt_3d ) )
790       ENDIF
791       IF ( time_do2d_xz >= dt_do2d_xz )  THEN
792          CALL data_output_2d( 'xz', 0 )
793          time_do2d_xz = MOD( time_do2d_xz, MAX( dt_do2d_xz, dt_3d ) )
794       ENDIF
795       IF ( time_do2d_yz >= dt_do2d_yz )  THEN
796          CALL data_output_2d( 'yz', 0 )
797          time_do2d_yz = MOD( time_do2d_yz, MAX( dt_do2d_yz, dt_3d ) )
798       ENDIF
799
800!
801!--    3d-data output (volume data)
802       IF ( time_do3d >= dt_do3d )  THEN
803          CALL data_output_3d( 0 )
804          time_do3d = MOD( time_do3d, MAX( dt_do3d, dt_3d ) )
805       ENDIF
806
807!
808!--    masked data output
809       DO  mid = 1, masks
810          IF ( time_domask(mid) >= dt_domask(mid) )  THEN
811             CALL data_output_mask( 0 )
812             time_domask(mid) = MOD( time_domask(mid),  &
813                                     MAX( dt_domask(mid), dt_3d ) )
814          ENDIF
815       ENDDO
816
817!
818!--    Output of time-averaged 2d/3d/masked data
819       IF ( time_do_av >= dt_data_output_av )  THEN
820          CALL average_3d_data
821          CALL data_output_2d( 'xy', 1 )
822          CALL data_output_2d( 'xz', 1 )
823          CALL data_output_2d( 'yz', 1 )
824          CALL data_output_3d( 1 )
825          DO  mid = 1, masks
826             CALL data_output_mask( 1 )
827          ENDDO
828          time_do_av = MOD( time_do_av, MAX( dt_data_output_av, dt_3d ) )
829       ENDIF
830
831!
832!--    Output of particle time series
833       IF ( particle_advection )  THEN
834          IF ( time_dopts >= dt_dopts  .OR. &
835               ( simulated_time >= particle_advection_start  .AND. &
836                 first_call_lpm ) )  THEN
837             CALL data_output_ptseries
838             time_dopts = MOD( time_dopts, MAX( dt_dopts, dt_3d ) )
839          ENDIF
840       ENDIF
841
842!
843!--    Output of dvrp-graphics (isosurface, particles, slicer)
844#if defined( __dvrp_graphics )
845       CALL DVRP_LOG_EVENT( -2, current_timestep_number-1 )
846#endif
847       IF ( time_dvrp >= dt_dvrp )  THEN
848          CALL data_output_dvrp
849          time_dvrp = MOD( time_dvrp, MAX( dt_dvrp, dt_3d ) )
850       ENDIF
851#if defined( __dvrp_graphics )
852       CALL DVRP_LOG_EVENT( 2, current_timestep_number )
853#endif
854
855!
856!--    If required, set the heat flux for the next time step at a random value
857       IF ( constant_heatflux  .AND.  random_heatflux )  CALL disturb_heatflux
858
859!
860!--    Execute user-defined actions
861       CALL user_actions( 'after_timestep' )
862
863       CALL cpu_log( log_point_s(10), 'timesteps', 'stop' )
864
865
866    ENDDO   ! time loop
867
868#if defined( __dvrp_graphics )
869    CALL DVRP_LOG_EVENT( -2, current_timestep_number )
870#endif
871
872 END SUBROUTINE time_integration
Note: See TracBrowser for help on using the repository browser.