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/init_cloud_physics.f90

    r1310 r1320  
    2020! Current revisions:
    2121! -----------------
     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 mod_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
    2229!
    2330! Former revisions:
     
    4148! calculation of b_cond replaced by calculation of bfactor
    4249!
    43 ! 221 2009-01-12 15:32:23Z raasch
    44 ! Bugfix: abort in case that absolute temperature is below zero
    45 !
    46 ! 95 2007-06-02 16:48:38Z raasch
    47 ! hydro_press renamed hyp
    48 !
    49 ! February 2007
    50 ! RCS Log replace by Id keyword, revision history cleaned up
    51 !
    52 ! Revision 1.5  2005/06/26 19:55:58  raasch
    53 ! Initialization of cloud droplet constants, gas_constant renamed r_d,
    54 ! latent_heat renamed l_v
    55 !
    5650! Revision 1.1  2000/04/13 14:37:22  schroeter
    5751! Initial revision
     
    6357!------------------------------------------------------------------------------!
    6458
    65     USE arrays_3d
    66     USE cloud_parameters
    67     USE constants
    68     USE control_parameters
    69     USE grid_variables
    70     USE indices
     59    USE arrays_3d,                                                             &
     60        ONLY:  dzu, hyp, pt_init, zu
     61       
     62    USE cloud_parameters,                                                      &
     63        ONLY:  bfactor, cp, c_sedimentation, dpirho_l, dt_precipitation,       &
     64               hyrho, l_d_cp, l_d_r, l_d_rv, l_v, mass_of_solute,              &
     65               molecular_weight_of_solute, molecular_weight_of_water, pirho_l, &
     66               pt_d_t, rho_l, r_d, r_v, schmidt, schmidt_p_1d3, t_d_pt,        &
     67               vanthoff, w_precipitation
     68       
     69    USE constants,                                                             &
     70        ONLY:  pi
     71       
     72    USE control_parameters,                                                    &
     73        ONLY:  g, icloud_scheme, message_string, precipitation, pt_surface,    &
     74               rho_surface, surface_pressure
     75   
     76    USE indices,                                                               &
     77        ONLY:  nzb, nzt
     78   
     79    USE kinds
    7180
    7281    IMPLICIT NONE
    7382
    74     INTEGER ::  k
    75     REAL    ::  t_surface
     83    INTEGER(iwp) ::  k      !:
     84   
     85    REAL(wp) ::  t_surface  !:
    7686
    7787    ALLOCATE( hyp(nzb:nzt+1), pt_d_t(nzb:nzt+1), t_d_pt(nzb:nzt+1),  &
Note: See TracChangeset for help on using the changeset viewer.