SUBROUTINE time_integration !------------------------------------------------------------------------------! ! Current revisions: ! ----------------- ! ! ! Former revisions: ! ----------------- ! $Id: time_integration.f90 484 2010-02-05 07:36:54Z maronga $ ! ! 449 2010-02-02 11:23:59Z raasch ! Bugfix: exchange of ghost points for prho included ! ! 410 2009-12-04 17:05:40Z letzel ! masked data output ! ! 388 2009-09-23 09:40:33Z raasch ! Using prho instead of rho in diffusvities. ! Coupling with independent precursor runs. ! Bugfix: output of particle time series only if particle advection is switched ! on ! ! 151 2008-03-07 13:42:18Z raasch ! inflow turbulence is imposed by calling new routine inflow_turbulence ! ! 108 2007-08-24 15:10:38Z letzel ! Call of new routine surface_coupler, ! presure solver is called after the first Runge-Kutta substep instead of the ! last in case that call_psolver_at_all_substeps = .F.; for this case, the ! random perturbation has to be added to the velocity fields also after the ! first substep ! ! 97 2007-06-21 08:23:15Z raasch ! diffusivities is called with argument rho in case of ocean runs, ! new argument pt_/prho_reference in calls of diffusivities, ! ghostpoint exchange for salinity and density ! ! 87 2007-05-22 15:46:47Z raasch ! var_hom renamed pr_palm ! ! 75 2007-03-22 09:54:05Z raasch ! Move call of user_actions( 'after_integration' ) below increment of times ! and counters, ! calls of prognostic_equations_.. changed to .._noopt, .._cache, and ! .._vector, these calls are now controlled by switch loop_optimization, ! uxrp, vynp eliminated, 2nd+3rd argument removed from exchange horiz, ! moisture renamed humidity ! ! RCS Log replace by Id keyword, revision history cleaned up ! ! Revision 1.8 2006/08/22 14:16:05 raasch ! Disturbances are imposed only for the last Runge-Kutta-substep ! ! Revision 1.2 2004/04/30 13:03:40 raasch ! decalpha-specific warning removed, routine name changed to time_integration, ! particle advection is carried out only once during the intermediate steps, ! impulse_advec renamed momentum_advec ! ! Revision 1.1 1997/08/11 06:19:04 raasch ! Initial revision ! ! ! Description: ! ------------ ! Integration in time of the model equations, statistical analysis and graphic ! output !------------------------------------------------------------------------------! USE arrays_3d USE averaging USE control_parameters USE cpulog #if defined( __dvrp_graphics ) USE DVRP #endif USE grid_variables USE indices USE interaction_droplets_ptq_mod USE interfaces USE particle_attributes USE pegrid USE prognostic_equations_mod USE statistics USE user_actions_mod IMPLICIT NONE CHARACTER (LEN=9) :: time_to_string INTEGER :: i, j, k ! !-- At the beginning of a simulation determine the time step as well as !-- determine and print out the run control parameters IF ( simulated_time == 0.0 ) CALL timestep CALL run_control ! !-- Data exchange between coupled models in case that a call has been omitted !-- at the end of the previous run of a job chain. IF ( coupling_mode /= 'uncoupled' .AND. run_coupled ) THEN ! !-- In case of model termination initiated by the local model the coupler !-- must not be called because this would again cause an MPI hang. DO WHILE ( time_coupling >= dt_coupling .AND. terminate_coupled == 0 ) CALL surface_coupler time_coupling = time_coupling - dt_coupling ENDDO IF (time_coupling == 0.0 .AND. time_since_reference_point < dt_coupling)& THEN time_coupling = time_since_reference_point ENDIF ENDIF #if defined( __dvrp_graphics ) ! !-- Time measurement with dvrp software CALL DVRP_LOG_EVENT( 2, current_timestep_number ) #endif ! !-- Start of the time loop DO WHILE ( simulated_time < end_time .AND. .NOT. stop_dt .AND. & .NOT. terminate_run ) CALL cpu_log( log_point_s(10), 'timesteps', 'start' ) ! !-- Determine size of next time step IF ( simulated_time /= 0.0 ) CALL timestep ! !-- Execute the user-defined actions CALL user_actions( 'before_timestep' ) ! !-- Start of intermediate step loop intermediate_timestep_count = 0 DO WHILE ( intermediate_timestep_count < & intermediate_timestep_count_max ) intermediate_timestep_count = intermediate_timestep_count + 1 ! !-- Set the steering factors for the prognostic equations which depend !-- on the timestep scheme CALL timestep_scheme_steering ! !-- Solve the prognostic equations. A fast cache optimized version with !-- only one single loop is used in case of Piascek-Williams advection !-- scheme. NEC vector machines use a different version, because !-- in the other versions a good vectorization is prohibited due to !-- inlining problems. IF ( loop_optimization == 'vector' ) THEN CALL prognostic_equations_vector ELSE IF ( momentum_advec == 'ups-scheme' .OR. & scalar_advec == 'ups-scheme' .OR. & scalar_advec == 'bc-scheme' ) & THEN CALL prognostic_equations_noopt ELSE CALL prognostic_equations_cache ENDIF ENDIF ! !-- Particle advection (only once during intermediate steps, because !-- it uses an Euler-step) IF ( particle_advection .AND. & simulated_time >= particle_advection_start .AND. & intermediate_timestep_count == 1 ) THEN CALL advec_particles first_call_advec_particles = .FALSE. ENDIF ! !-- Interaction of droplets with temperature and specific humidity. !-- Droplet condensation and evaporation is calculated within !-- advec_particles. IF ( cloud_droplets .AND. & intermediate_timestep_count == intermediate_timestep_count_max )& THEN CALL interaction_droplets_ptq ENDIF ! !-- Exchange of ghost points (lateral boundary conditions) CALL cpu_log( log_point(26), 'exchange-horiz-progn', 'start' ) CALL exchange_horiz( u_p ) CALL exchange_horiz( v_p ) CALL exchange_horiz( w_p ) CALL exchange_horiz( pt_p ) IF ( .NOT. constant_diffusion ) CALL exchange_horiz( e_p ) IF ( ocean ) THEN CALL exchange_horiz( sa_p ) CALL exchange_horiz( rho ) CALL exchange_horiz( prho ) ENDIF IF ( humidity .OR. passive_scalar ) CALL exchange_horiz( q_p ) IF ( cloud_droplets ) THEN CALL exchange_horiz( ql ) CALL exchange_horiz( ql_c ) CALL exchange_horiz( ql_v ) CALL exchange_horiz( ql_vp ) ENDIF CALL cpu_log( log_point(26), 'exchange-horiz-progn', 'stop' ) ! !-- Apply time filter in case of leap-frog timestep IF ( tsc(2) == 2.0 .AND. timestep_scheme(1:8) == 'leapfrog' ) THEN CALL asselin_filter ENDIF ! !-- Boundary conditions for the prognostic quantities (except of the !-- velocities at the outflow in case of a non-cyclic lateral wall) CALL boundary_conds( 'main' ) ! !-- Swap the time levels in preparation for the next time step. CALL swap_timelevel ! !-- Temperature offset must be imposed at cyclic boundaries in x-direction !-- when a sloping surface is used IF ( sloping_surface ) THEN IF ( nxl == 0 ) pt(:,:,nxl-1) = pt(:,:,nxl-1) - pt_slope_offset IF ( nxr == nx ) pt(:,:,nxr+1) = pt(:,:,nxr+1) + pt_slope_offset ENDIF ! !-- Impose a turbulent inflow using the recycling method IF ( turbulent_inflow ) CALL inflow_turbulence ! !-- Impose a random perturbation on the horizontal velocity field IF ( create_disturbances .AND. & ( call_psolver_at_all_substeps .AND. & intermediate_timestep_count == intermediate_timestep_count_max )& .OR. ( .NOT. call_psolver_at_all_substeps .AND. & intermediate_timestep_count == 1 ) ) & THEN time_disturb = time_disturb + dt_3d IF ( time_disturb >= dt_disturb ) THEN IF ( hom(nzb+5,1,pr_palm,0) < disturbance_energy_limit ) THEN CALL disturb_field( nzb_u_inner, tend, u ) CALL disturb_field( nzb_v_inner, tend, v ) ELSEIF ( bc_lr /= 'cyclic' .OR. bc_ns /= 'cyclic' ) THEN ! !-- Runs with a non-cyclic lateral wall need perturbations !-- near the inflow throughout the whole simulation dist_range = 1 CALL disturb_field( nzb_u_inner, tend, u ) CALL disturb_field( nzb_v_inner, tend, v ) dist_range = 0 ENDIF time_disturb = time_disturb - dt_disturb ENDIF ENDIF ! !-- Reduce the velocity divergence via the equation for perturbation !-- pressure. IF ( intermediate_timestep_count == 1 .OR. & call_psolver_at_all_substeps ) THEN CALL pres ENDIF ! !-- If required, compute virtuell potential temperature IF ( humidity ) CALL compute_vpt ! !-- If required, compute liquid water content IF ( cloud_physics ) CALL calc_liquid_water_content ! !-- Compute the diffusion quantities IF ( .NOT. constant_diffusion ) THEN ! !-- First the vertical fluxes in the Prandtl layer are being computed IF ( prandtl_layer ) THEN CALL cpu_log( log_point(19), 'prandtl_fluxes', 'start' ) CALL prandtl_fluxes CALL cpu_log( log_point(19), 'prandtl_fluxes', 'stop' ) ENDIF ! !-- Compute the diffusion coefficients CALL cpu_log( log_point(17), 'diffusivities', 'start' ) IF ( .NOT. humidity ) THEN IF ( ocean ) THEN CALL diffusivities( prho, prho_reference ) ELSE CALL diffusivities( pt, pt_reference ) ENDIF ELSE CALL diffusivities( vpt, pt_reference ) ENDIF CALL cpu_log( log_point(17), 'diffusivities', 'stop' ) ENDIF ENDDO ! Intermediate step loop ! !-- Increase simulation time and output times current_timestep_number = current_timestep_number + 1 simulated_time = simulated_time + dt_3d simulated_time_chr = time_to_string( simulated_time ) time_since_reference_point = simulated_time - coupling_start_time IF ( simulated_time >= skip_time_data_output_av ) THEN time_do_av = time_do_av + dt_3d ENDIF IF ( simulated_time >= skip_time_do2d_xy ) THEN time_do2d_xy = time_do2d_xy + dt_3d ENDIF IF ( simulated_time >= skip_time_do2d_xz ) THEN time_do2d_xz = time_do2d_xz + dt_3d ENDIF IF ( simulated_time >= skip_time_do2d_yz ) THEN time_do2d_yz = time_do2d_yz + dt_3d ENDIF IF ( simulated_time >= skip_time_do3d ) THEN time_do3d = time_do3d + dt_3d ENDIF DO mid = 1, masks IF ( simulated_time >= skip_time_domask(mid) ) THEN time_domask(mid)= time_domask(mid) + dt_3d ENDIF ENDDO time_dvrp = time_dvrp + dt_3d IF ( simulated_time >= skip_time_dosp ) THEN time_dosp = time_dosp + dt_3d ENDIF time_dots = time_dots + dt_3d IF ( .NOT. first_call_advec_particles ) THEN time_dopts = time_dopts + dt_3d ENDIF IF ( simulated_time >= skip_time_dopr ) THEN time_dopr = time_dopr + dt_3d ENDIF time_dopr_listing = time_dopr_listing + dt_3d time_run_control = time_run_control + dt_3d ! !-- Data exchange between coupled models IF ( coupling_mode /= 'uncoupled' .AND. run_coupled ) THEN time_coupling = time_coupling + dt_3d ! !-- In case of model termination initiated by the local model !-- (terminate_coupled > 0), the coupler must be skipped because it would !-- cause an MPI intercomminucation hang. !-- If necessary, the coupler will be called at the beginning of the !-- next restart run. DO WHILE ( time_coupling >= dt_coupling .AND. terminate_coupled == 0 ) CALL surface_coupler time_coupling = time_coupling - dt_coupling ENDDO ENDIF ! !-- Execute user-defined actions CALL user_actions( 'after_integration' ) ! !-- If Galilei transformation is used, determine the distance that the !-- model has moved so far IF ( galilei_transformation ) THEN advected_distance_x = advected_distance_x + u_gtrans * dt_3d advected_distance_y = advected_distance_y + v_gtrans * dt_3d ENDIF ! !-- Check, if restart is necessary (because cpu-time is expiring or !-- because it is forced by user) and set stop flag !-- This call is skipped if the remote model has already initiated a restart. IF ( .NOT. terminate_run ) CALL check_for_restart ! !-- Carry out statistical analysis and output at the requested output times. !-- The MOD function is used for calculating the output time counters (like !-- time_dopr) in order to regard a possible decrease of the output time !-- interval in case of restart runs ! !-- Set a flag indicating that so far no statistics have been created !-- for this time step flow_statistics_called = .FALSE. ! !-- If required, call flow_statistics for averaging in time IF ( averaging_interval_pr /= 0.0 .AND. & ( dt_dopr - time_dopr ) <= averaging_interval_pr .AND. & simulated_time >= skip_time_dopr ) THEN time_dopr_av = time_dopr_av + dt_3d IF ( time_dopr_av >= dt_averaging_input_pr ) THEN do_sum = .TRUE. time_dopr_av = MOD( time_dopr_av, & MAX( dt_averaging_input_pr, dt_3d ) ) ENDIF ENDIF IF ( do_sum ) CALL flow_statistics ! !-- Sum-up 3d-arrays for later output of time-averaged 2d/3d/masked data IF ( averaging_interval /= 0.0 .AND. & ( dt_data_output_av - time_do_av ) <= averaging_interval .AND. & simulated_time >= skip_time_data_output_av ) & THEN time_do_sla = time_do_sla + dt_3d IF ( time_do_sla >= dt_averaging_input ) THEN CALL sum_up_3d_data average_count_3d = average_count_3d + 1 time_do_sla = MOD( time_do_sla, MAX( dt_averaging_input, dt_3d ) ) ENDIF ENDIF ! !-- Calculate spectra for time averaging IF ( averaging_interval_sp /= 0.0 .AND. & ( dt_dosp - time_dosp ) <= averaging_interval_sp .AND. & simulated_time >= skip_time_dosp ) THEN time_dosp_av = time_dosp_av + dt_3d IF ( time_dosp_av >= dt_averaging_input_pr ) THEN CALL calc_spectra time_dosp_av = MOD( time_dosp_av, & MAX( dt_averaging_input_pr, dt_3d ) ) ENDIF ENDIF ! !-- Computation and output of run control parameters. !-- This is also done whenever the time step has changed or perturbations !-- have been imposed IF ( time_run_control >= dt_run_control .OR. & ( dt_changed .AND. timestep_scheme(1:5) /= 'runge' ) .OR. & disturbance_created ) & THEN CALL run_control IF ( time_run_control >= dt_run_control ) THEN time_run_control = MOD( time_run_control, & MAX( dt_run_control, dt_3d ) ) ENDIF ENDIF ! !-- Profile output (ASCII) on file IF ( time_dopr_listing >= dt_dopr_listing ) THEN CALL print_1d time_dopr_listing = MOD( time_dopr_listing, MAX( dt_dopr_listing, & dt_3d ) ) ENDIF ! !-- Graphic output for PROFIL IF ( time_dopr >= dt_dopr ) THEN IF ( dopr_n /= 0 ) CALL data_output_profiles time_dopr = MOD( time_dopr, MAX( dt_dopr, dt_3d ) ) time_dopr_av = 0.0 ! due to averaging (see above) ENDIF ! !-- Graphic output for time series IF ( time_dots >= dt_dots ) THEN CALL data_output_tseries time_dots = MOD( time_dots, MAX( dt_dots, dt_3d ) ) ENDIF ! !-- Output of spectra (formatted for use with PROFIL), in case of no !-- time averaging, spectra has to be calculated before IF ( time_dosp >= dt_dosp ) THEN IF ( average_count_sp == 0 ) CALL calc_spectra CALL data_output_spectra time_dosp = MOD( time_dosp, MAX( dt_dosp, dt_3d ) ) ENDIF ! !-- 2d-data output (cross-sections) IF ( time_do2d_xy >= dt_do2d_xy ) THEN CALL data_output_2d( 'xy', 0 ) time_do2d_xy = MOD( time_do2d_xy, MAX( dt_do2d_xy, dt_3d ) ) ENDIF IF ( time_do2d_xz >= dt_do2d_xz ) THEN CALL data_output_2d( 'xz', 0 ) time_do2d_xz = MOD( time_do2d_xz, MAX( dt_do2d_xz, dt_3d ) ) ENDIF IF ( time_do2d_yz >= dt_do2d_yz ) THEN CALL data_output_2d( 'yz', 0 ) time_do2d_yz = MOD( time_do2d_yz, MAX( dt_do2d_yz, dt_3d ) ) ENDIF ! !-- 3d-data output (volume data) IF ( time_do3d >= dt_do3d ) THEN CALL data_output_3d( 0 ) time_do3d = MOD( time_do3d, MAX( dt_do3d, dt_3d ) ) ENDIF ! !-- masked data output DO mid = 1, masks IF ( time_domask(mid) >= dt_domask(mid) ) THEN CALL data_output_mask( 0 ) time_domask(mid) = MOD( time_domask(mid), & MAX( dt_domask(mid), dt_3d ) ) ENDIF ENDDO ! !-- Output of time-averaged 2d/3d/masked data IF ( time_do_av >= dt_data_output_av ) THEN CALL average_3d_data CALL data_output_2d( 'xy', 1 ) CALL data_output_2d( 'xz', 1 ) CALL data_output_2d( 'yz', 1 ) CALL data_output_3d( 1 ) DO mid = 1, masks CALL data_output_mask( 1 ) ENDDO time_do_av = MOD( time_do_av, MAX( dt_data_output_av, dt_3d ) ) ENDIF ! !-- Output of particle time series IF ( particle_advection ) THEN IF ( time_dopts >= dt_dopts .OR. & ( simulated_time >= particle_advection_start .AND. & first_call_advec_particles ) ) THEN CALL data_output_ptseries time_dopts = MOD( time_dopts, MAX( dt_dopts, dt_3d ) ) ENDIF ENDIF ! !-- Output of dvrp-graphics (isosurface, particles, slicer) #if defined( __dvrp_graphics ) CALL DVRP_LOG_EVENT( -2, current_timestep_number-1 ) #endif IF ( time_dvrp >= dt_dvrp ) THEN CALL data_output_dvrp time_dvrp = MOD( time_dvrp, MAX( dt_dvrp, dt_3d ) ) ENDIF #if defined( __dvrp_graphics ) CALL DVRP_LOG_EVENT( 2, current_timestep_number ) #endif ! !-- If required, set the heat flux for the next time step at a random value IF ( constant_heatflux .AND. random_heatflux ) CALL disturb_heatflux ! !-- Execute user-defined actions CALL user_actions( 'after_timestep' ) CALL cpu_log( log_point_s(10), 'timesteps', 'stop' ) ENDDO ! time loop #if defined( __dvrp_graphics ) CALL DVRP_LOG_EVENT( -2, current_timestep_number ) #endif END SUBROUTINE time_integration