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/prognostic_equations.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:
     
    8793! temperature equation can be switched off
    8894!
    89 ! 785 2011-11-28 09:47:19Z raasch
    90 ! new factor rdf_sc allows separate Rayleigh damping of scalars
    91 !
    92 ! 736 2011-08-17 14:13:26Z suehring
    93 ! Bugfix: determination of first thread index i for WS-scheme
    94 !
    95 ! 709 2011-03-30 09:31:40Z raasch
    96 ! formatting adjustments
    97 !
    98 ! 673 2011-01-18 16:19:48Z suehring
    99 ! Consideration of the pressure gradient (steered by tsc(4)) during the time
    100 ! integration removed.
    101 !
    102 ! 667 2010-12-23 12:06:00Z suehring/gryschka
    103 ! Calls of the advection routines with WS5 added.
    104 ! Calls of ws_statistics added to set the statistical arrays to zero after each
    105 ! time step.
    106 !
    107 ! 531 2010-04-21 06:47:21Z heinze
    108 ! add call of subsidence in the equation for humidity / passive scalar
    109 !
    110 ! 411 2009-12-11 14:15:58Z heinze
    111 ! add call of subsidence in the equation for potential temperature
    112 !
    113 ! 388 2009-09-23 09:40:33Z raasch
    114 ! prho is used instead of rho in diffusion_e,
    115 ! external pressure gradient
    116 !
    117 ! 153 2008-03-19 09:41:30Z steinfeld
    118 ! add call of plant_canopy_model in the prognostic equation for
    119 ! the potential temperature and for the passive scalar
    120 !
    121 ! 138 2007-11-28 10:03:58Z letzel
    122 ! add call of subroutines that evaluate the canopy drag terms,
    123 ! add wall_*flux to parameter list of calls of diffusion_s
    124 !
    125 ! 106 2007-08-16 14:30:26Z raasch
    126 ! +uswst, vswst as arguments in calls of diffusion_u|v,
    127 ! loops for u and v are starting from index nxlu, nysv, respectively (needed
    128 ! for non-cyclic boundary conditions)
    129 !
    130 ! 97 2007-06-21 08:23:15Z raasch
    131 ! prognostic equation for salinity, density is calculated from equation of
    132 ! state for seawater and is used for calculation of buoyancy,
    133 ! +eqn_state_seawater_mod
    134 ! diffusion_e is called with argument rho in case of ocean runs,
    135 ! new argument zw in calls of diffusion_e, new argument pt_/prho_reference
    136 ! in calls of buoyancy and diffusion_e, calc_mean_pt_profile renamed
    137 ! calc_mean_profile
    138 !
    139 ! 75 2007-03-22 09:54:05Z raasch
    140 ! checking for negative q and limiting for positive values,
    141 ! z0 removed from arguments in calls of diffusion_u/v/w, uxrp, vynp eliminated,
    142 ! subroutine names changed to .._noopt, .._cache, and .._vector,
    143 ! moisture renamed humidity, Bott-Chlond-scheme can be used in the
    144 ! _vector-version
    145 !
    146 ! 19 2007-02-23 04:53:48Z raasch
    147 ! Calculation of e, q, and pt extended for gridpoint nzt,
    148 ! handling of given temperature/humidity/scalar fluxes at top surface
    149 !
    150 ! RCS Log replace by Id keyword, revision history cleaned up
    151 !
    152 ! Revision 1.21  2006/08/04 15:01:07  raasch
    153 ! upstream scheme can be forced to be used for tke (use_upstream_for_tke)
    154 ! regardless of the timestep scheme used for the other quantities,
    155 ! new argument diss in call of diffusion_e
    156 !
    15795! Revision 1.1  2000/04/13 14:56:27  schroeter
    15896! Initial revision
     
    164102!------------------------------------------------------------------------------!
    165103
    166     USE arrays_3d
    167     USE control_parameters
    168     USE cpulog
    169     USE eqn_state_seawater_mod
    170     USE grid_variables
    171     USE indices
    172     USE pegrid
    173     USE pointer_interfaces
    174     USE statistics
    175     USE advec_ws
    176     USE advec_s_pw_mod
    177     USE advec_s_up_mod
    178     USE advec_u_pw_mod
    179     USE advec_u_up_mod
    180     USE advec_v_pw_mod
    181     USE advec_v_up_mod
    182     USE advec_w_pw_mod
    183     USE advec_w_up_mod
    184     USE buoyancy_mod
    185     USE calc_precipitation_mod
    186     USE calc_radiation_mod
    187     USE coriolis_mod
    188     USE diffusion_e_mod
    189     USE diffusion_s_mod
    190     USE diffusion_u_mod
    191     USE diffusion_v_mod
    192     USE diffusion_w_mod
    193     USE impact_of_latent_heat_mod
    194     USE microphysics_mod
    195     USE nudge_mod
    196     USE plant_canopy_model_mod
    197     USE production_e_mod
    198     USE subsidence_mod
    199     USE user_actions_mod
     104    USE arrays_3d,                                                             &
     105        ONLY:  diss_l_e, diss_l_nr, diss_l_pt, diss_l_q, diss_l_qr,            &
     106               diss_l_sa, diss_s_e, diss_s_nr, diss_s_pt, diss_s_q,            &
     107               diss_s_qr, diss_s_sa, e, e_p, flux_s_e, flux_s_nr, flux_s_pt,   &
     108               flux_s_q, flux_s_qr, flux_s_sa, flux_l_e, flux_l_nr,            &
     109               flux_l_pt, flux_l_q, flux_l_qr, flux_l_sa, nr, nr_p, nrsws,     &
     110               nrswst, pt, ptdf_x, ptdf_y, pt_init, pt_p, prho, q, q_init,     &
     111               q_p, qsws, qswst, qr, qr_p, qrsws, qrswst, rdf, rdf_sc, rho,    &
     112               sa, sa_init, sa_p, saswsb, saswst, shf, tend, tend_nr,          &
     113               tend_pt, tend_q, tend_qr, te_m, tnr_m, tpt_m, tq_m, tqr_m,      &
     114               tsa_m, tswst, tu_m, tv_m, tw_m, u, ug, u_p, v, vg, vpt, v_p,    &
     115               w, w_p
     116       
     117    USE control_parameters,                                                    &
     118        ONLY:  cloud_physics, constant_diffusion, cthf, dp_external,           &
     119               dp_level_ind_b, dp_smooth_factor, dpdxy, dt_3d, humidity,       &
     120               icloud_scheme, inflow_l, intermediate_timestep_count,           &
     121               intermediate_timestep_count_max, large_scale_subsidence,        &
     122               neutral, nudging, ocean, outflow_l, outflow_s, passive_scalar,  &
     123               plant_canopy, precipitation, prho_reference, prho_reference,    &
     124               prho_reference, pt_reference, pt_reference, pt_reference,       &
     125               radiation, scalar_advec, scalar_advec, simulated_time,          &
     126               sloping_surface, timestep_scheme, tsc, use_upstream_for_tke,    &
     127               use_upstream_for_tke, use_upstream_for_tke, wall_heatflux,      &
     128               wall_nrflux, wall_qflux, wall_qflux, wall_qflux, wall_qrflux,   &
     129               wall_salinityflux, ws_scheme_mom, ws_scheme_sca
     130
     131    USE cpulog,                                                                &
     132        ONLY:  cpu_log, log_point
     133
     134    USE eqn_state_seawater_mod,                                                &
     135        ONLY:  eqn_state_seawater
     136
     137    USE indices,                                                               &
     138        ONLY:  i_left, i_right, j_north, j_south, nxl, nxlu, nxr, nyn, nys,    &
     139               nysv, nzb_s_inner, nzb_u_inner, nzb_v_inner, nzb_w_inner, nzt
     140
     141    USE advec_ws,                                                              &
     142        ONLY:  advec_s_ws, advec_s_ws_acc, advec_u_ws, advec_u_ws_acc,         &
     143               advec_v_ws, advec_v_ws_acc, advec_w_ws, advec_w_ws_acc
     144
     145    USE advec_s_pw_mod,                                                        &
     146        ONLY:  advec_s_pw
     147
     148    USE advec_s_up_mod,                                                        &
     149        ONLY:  advec_s_up
     150
     151    USE advec_u_pw_mod,                                                        &
     152        ONLY:  advec_u_pw
     153
     154    USE advec_u_up_mod,                                                        &
     155        ONLY:  advec_u_up
     156
     157    USE advec_v_pw_mod,                                                        &
     158        ONLY:  advec_v_pw
     159
     160    USE advec_v_up_mod,                                                        &
     161        ONLY:  advec_v_up
     162
     163    USE advec_w_pw_mod,                                                        &
     164        ONLY:  advec_w_pw
     165
     166    USE advec_w_up_mod,                                                        &
     167        ONLY:  advec_w_up
     168
     169    USE buoyancy_mod,                                                          &
     170        ONLY:  buoyancy, buoyancy_acc
     171
     172    USE calc_precipitation_mod,                                                &
     173        ONLY:  calc_precipitation
     174
     175    USE calc_radiation_mod,                                                    &
     176        ONLY:  calc_radiation
     177 
     178    USE coriolis_mod,                                                          &
     179        ONLY:  coriolis, coriolis_acc
     180
     181    USE diffusion_e_mod,                                                       &
     182        ONLY:  diffusion_e, diffusion_e_acc
     183
     184    USE diffusion_s_mod,                                                       &
     185        ONLY:  diffusion_s, diffusion_s_acc
     186
     187    USE diffusion_u_mod,                                                       &
     188        ONLY:  diffusion_u, diffusion_u_acc
     189
     190    USE diffusion_v_mod,                                                       &
     191        ONLY:  diffusion_v, diffusion_v_acc
     192
     193    USE diffusion_w_mod,                                                       &
     194        ONLY:  diffusion_w, diffusion_w_acc
     195
     196    USE impact_of_latent_heat_mod,                                             &
     197        ONLY:  impact_of_latent_heat
     198
     199    USE kinds
     200
     201    USE microphysics_mod,                                                      &
     202        ONLY:  microphysics_control
     203
     204    USE nudge_mod,                                                             &
     205        ONLY:  nudge
     206
     207    USE plant_canopy_model_mod,                                                &
     208        ONLY:  plant_canopy_model
     209
     210    USE production_e_mod,                                                      &
     211        ONLY:  production_e, production_e_acc
     212
     213    USE subsidence_mod,                                                        &
     214        ONLY:  subsidence
     215
     216    USE user_actions_mod,                                                      &
     217        ONLY:  user_actions
    200218
    201219
     
    235253    IMPLICIT NONE
    236254
    237     INTEGER ::  i, i_omp_start, j, k, omp_get_thread_num, tn = 0
    238     LOGICAL ::  loop_start
     255    INTEGER(iwp) ::  i                   !:
     256    INTEGER(iwp) ::  i_omp_start         !:
     257    INTEGER(iwp) ::  j                   !:
     258    INTEGER(iwp) ::  k                   !:
     259    INTEGER(iwp) ::  omp_get_thread_num  !:
     260    INTEGER(iwp) ::  tn = 0              !:
     261   
     262    LOGICAL      ::  loop_start          !:
    239263
    240264
     
    835859    IMPLICIT NONE
    836860
    837     INTEGER ::  i, j, k
    838     REAL    ::  sbt
     861    INTEGER(iwp) ::  i    !:
     862    INTEGER(iwp) ::  j    !:
     863    INTEGER(iwp) ::  k    !:
     864
     865    REAL(wp)     ::  sbt  !:
    839866
    840867
     
    14791506    IMPLICIT NONE
    14801507
    1481     INTEGER ::  i, j, k, runge_step
    1482     REAL    ::  sbt
     1508    INTEGER(iwp) ::  i           !:
     1509    INTEGER(iwp) ::  j           !:
     1510    INTEGER(iwp) ::  k           !:
     1511    INTEGER(iwp) ::  runge_step  !:
     1512
     1513    REAL(wp)     ::  sbt         !:
    14831514
    14841515!
Note: See TracChangeset for help on using the changeset viewer.