Ignore:
Timestamp:
Mar 20, 2014 8:40:49 AM (10 years ago)
Author:
raasch
Message:

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/time_integration.f90

    r1319 r1320  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! ONLY-attribute added to USE-statements,
     23! kind-parameters added to all INTEGER and REAL declaration statements,
     24! kinds are defined in new module kinds,
     25! old module precision_kind is removed,
     26! revision history before 2012 removed,
     27! comment fields (!:) to be used for variable explanations added to
     28! all variable declaration statements
    2329!
    2430! Former revisions:
     
    101107! wang_collision_kernel renamed wang_kernel
    102108!
    103 ! 790 2011-11-29 03:11:20Z raasch
    104 ! exchange of ghostpoints for array diss
    105 !
    106 ! 707 2011-03-29 11:39:40Z raasch
    107 ! bc_lr/ns replaced by bc_lr/ns_cyc, calls of exchange_horiz are modified,
    108 ! adaption to sloping surface
    109 !
    110 ! 667  2010-12-23 12:06:00Z suehring/gryschka
    111 ! Calls of exchange_horiz are modified.
    112 ! Adaption to slooping surface.
    113 !
    114 ! 449 2010-02-02 11:23:59Z raasch
    115 ! Bugfix: exchange of ghost points for prho included
    116 !
    117 ! 410 2009-12-04 17:05:40Z letzel
    118 ! masked data output
    119 !
    120 ! 388 2009-09-23 09:40:33Z raasch
    121 ! Using prho instead of rho in diffusvities.
    122 ! Coupling with independent precursor runs.
    123 ! Bugfix: output of particle time series only if particle advection is switched
    124 !         on
    125 !
    126 ! 151 2008-03-07 13:42:18Z raasch
    127 ! inflow turbulence is imposed by calling new routine inflow_turbulence
    128 !
    129 ! 108 2007-08-24 15:10:38Z letzel
    130 ! Call of new routine surface_coupler,
    131 ! presure solver is called after the first Runge-Kutta substep instead of the
    132 ! last in case that call_psolver_at_all_substeps = .F.; for this case, the
    133 ! random perturbation has to be added to the velocity fields also after the
    134 ! first substep
    135 !
    136 ! 97 2007-06-21 08:23:15Z raasch
    137 ! diffusivities is called with argument rho in case of ocean runs,
    138 ! new argument pt_/prho_reference in calls of diffusivities,
    139 ! ghostpoint exchange for salinity and density
    140 !
    141 ! 87 2007-05-22 15:46:47Z raasch
    142 ! var_hom renamed pr_palm
    143 !
    144 ! 75 2007-03-22 09:54:05Z raasch
    145 ! Move call of user_actions( 'after_integration' ) below increment of times
    146 ! and counters,
    147 ! calls of prognostic_equations_.. changed to .._noopt, .._cache, and
    148 ! .._vector, these calls are now controlled by switch loop_optimization,
    149 ! uxrp, vynp eliminated, 2nd+3rd argument removed from exchange horiz,
    150 ! moisture renamed humidity
    151 !
    152 ! RCS Log replace by Id keyword, revision history cleaned up
    153 !
    154 ! Revision 1.8  2006/08/22 14:16:05  raasch
    155 ! Disturbances are imposed only for the last Runge-Kutta-substep
    156 !
    157 ! Revision 1.2  2004/04/30 13:03:40  raasch
    158 ! decalpha-specific warning removed, routine name changed to time_integration,
    159 ! particle advection is carried out only once during the intermediate steps,
    160 ! impulse_advec renamed momentum_advec
    161 !
    162109! Revision 1.1  1997/08/11 06:19:04  raasch
    163110! Initial revision
     
    170117!------------------------------------------------------------------------------!
    171118
    172     USE advec_ws
    173     USE arrays_3d
    174     USE averaging
    175     USE buoyancy_mod
    176     USE control_parameters
    177     USE cpulog
    178 #if defined( __dvrp_graphics )
    179     USE DVRP
    180 #endif
    181     USE grid_variables
    182     USE indices
    183     USE interaction_droplets_ptq_mod
    184     USE ls_forcing_mod
    185     USE particle_attributes
     119    USE advec_ws,                                                              &
     120        ONLY:  ws_statistics
     121
     122    USE arrays_3d,                                                             &
     123        ONLY:  diss, e_p, nr_p, prho, pt, pt_p, ql, ql_c, ql_v, ql_vp, qr_p,   &
     124               q_p, rho, sa_p, tend, u, u_p, v, vpt, v_p, w_p
     125
     126    USE buoyancy_mod,                                                          &
     127        ONLY:  calc_mean_profile
     128
     129    USE control_parameters,                                                    &
     130        ONLY:  advected_distance_x, advected_distance_y, average_count_3d,     &
     131               average_count_sp, averaging_interval, averaging_interval_pr,    &
     132               averaging_interval_sp, bc_lr_cyc, bc_ns_cyc,                    &
     133               call_psolver_at_all_substeps, cloud_droplets, cloud_physics,    &
     134               constant_heatflux, create_disturbances, dopr_n,                 &
     135               constant_diffusion, coupling_mode, coupling_start_time,         &
     136               current_timestep_number, disturbance_created,                   &
     137               disturbance_energy_limit, dist_range, do_sum, dt_3d,            &
     138               dt_averaging_input, dt_averaging_input_pr, dt_coupling,         &
     139               dt_data_output_av, dt_disturb, dt_do2d_xy, dt_do2d_xz,          &
     140               dt_do2d_yz, dt_do3d, dt_domask,dt_dopts, dt_dopr,               &
     141               dt_dopr_listing, dt_dosp, dt_dots, dt_dvrp, dt_run_control,     &
     142               end_time, first_call_lpm, galilei_transformation, humidity,     &
     143               icloud_scheme, intermediate_timestep_count,                     &
     144               intermediate_timestep_count_max, large_scale_forcing,           &
     145               loop_optimization, lsf_surf, lsf_vert, masks, mid,              &
     146               netcdf_data_format, neutral, nr_timesteps_this_run, ocean,      &
     147               on_device, passive_scalar, prandtl_layer, precipitation,        &
     148               prho_reference, pt_reference, pt_slope_offset, random_heatflux, &
     149               run_coupled, simulated_time, simulated_time_chr,                &
     150               skip_time_do2d_xy, skip_time_do2d_xz, skip_time_do2d_yz,        &
     151               skip_time_do3d, skip_time_domask, skip_time_dopr,               &
     152               skip_time_dosp, skip_time_data_output_av, sloping_surface,      &
     153               stop_dt, terminate_coupled, terminate_run, timestep_scheme,     &
     154               time_coupling, time_do2d_xy, time_do2d_xz, time_do2d_yz,        &
     155               time_do3d, time_domask, time_dopr, time_dopr_av,                &
     156               time_dopr_listing, time_dopts, time_dosp, time_dosp_av,         &
     157               time_dots, time_do_av, time_do_sla, time_disturb, time_dvrp,    &
     158               time_run_control, time_since_reference_point, turbulence,       &
     159               turbulent_inflow, use_initial_profile_as_reference,             &
     160               use_single_reference_value, u_gtrans, v_gtrans, ws_scheme_mom,  &
     161               ws_scheme_sca
     162
     163    USE cpulog,                                                                &
     164        ONLY:  cpu_log, log_point, log_point_s
     165
     166    USE indices,                                                               &
     167        ONLY:  i_left, i_right, j_north, j_south, nbgp, nx, nxl, nxlg, nxr,    &
     168               nxrg, nyn, nys, nzb, nzb_u_inner, nzb_v_inner
     169
     170    USE interaction_droplets_ptq_mod,                                          &
     171        ONLY:  interaction_droplets_ptq
     172
     173    USE kinds
     174
     175    USE ls_forcing_mod,                                                        &
     176        ONLY:  ls_forcing_surf, ls_forcing_vert
     177
     178    USE particle_attributes,                                                   &
     179        ONLY:  particle_advection, particle_advection_start, wang_kernel
     180
    186181    USE pegrid
    187     USE production_e_mod
    188     USE prognostic_equations_mod
    189     USE statistics
    190     USE user_actions_mod
     182
     183    USE production_e_mod,                                                      &
     184        ONLY:  production_e_init
     185
     186    USE prognostic_equations_mod,                                              &
     187        ONLY:  prognostic_equations_acc, prognostic_equations_cache,           &
     188               prognostic_equations_vector
     189
     190    USE statistics,                                                            &
     191        ONLY:  flow_statistics_called, hom, pr_palm
     192
     193    USE user_actions_mod,                                                      &
     194        ONLY:  user_actions
    191195
    192196    IMPLICIT NONE
    193197
    194     CHARACTER (LEN=9) ::  time_to_string
    195     INTEGER           ::  netcdf_data_format_save
     198    CHARACTER (LEN=9) ::  time_to_string          !:
     199
     200    INTEGER(iwp)      ::  netcdf_data_format_save !:
    196201
    197202!
Note: See TracChangeset for help on using the changeset viewer.