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

    r1310 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:
     
    2834! 1036 2012-10-22 13:43:42Z raasch
    2935! code put under GPL (PALM 3.9)
    30 !
    31 ! 72 2007-03-19 08:20:46Z
    32 ! precipitation_rate renamed dqdt_precip
    33 !
    34 ! 19 2007-02-23 04:53:48Z raasch
    35 ! Calculation extended for gridpoint nzt
    36 !
    37 ! RCS Log replace by Id keyword, revision history cleaned up
    38 !
    39 ! Revision 1.5  2004/01/30 10:25:59  raasch
    40 ! Scalar lower k index nzb replaced by 2d-array nzb_2d
    4136!
    4237! Revision 1.1  2000/04/13 14:48:40  schroeter
     
    6661    SUBROUTINE impact_of_latent_heat
    6762
    68        USE arrays_3d
    69        USE cloud_parameters
    70        USE constants
    71        USE indices
     63       USE arrays_3d,                                                          &
     64           ONLY:  ql, tend
     65           
     66       USE cloud_parameters,                                                   &
     67           ONLY:  l_d_cp, prec_time_const, pt_d_t, ql_crit
     68           
     69       USE indices,                                                            &
     70           ONLY:  nxl, nxr, nyn, nys, nzb_2d, nzt
     71           
     72       USE kinds
    7273
    7374       IMPLICIT NONE
    7475
    75        INTEGER ::  i, j, k
    76        REAL    ::  dqdt_precip
     76       INTEGER(iwp) ::  i  !:
     77       INTEGER(iwp) ::  j  !:
     78       INTEGER(iwp) ::  k  !:
     79       
     80       REAL(wp) ::  dqdt_precip  !:
    7781
    7882 
     
    100104    SUBROUTINE impact_of_latent_heat_ij( i, j )
    101105
    102        USE arrays_3d
    103        USE cloud_parameters
    104        USE constants
    105        USE indices
     106       USE arrays_3d,                                                          &
     107           ONLY:  ql, tend
     108           
     109       USE cloud_parameters,                                                   &
     110           ONLY:  l_d_cp, prec_time_const, pt_d_t, ql_crit
     111           
     112       USE indices,                                                            &
     113           ONLY:  nzb_2d, nzt
     114           
     115       USE kinds                                                               
    106116   
    107117       IMPLICIT NONE
    108118
    109        INTEGER ::  i, j, k
    110        REAL    ::  dqdt_precip
     119       INTEGER(iwp) ::  i  !:
     120       INTEGER(iwp) ::  j  !:
     121       INTEGER(iwp) ::  k  !:
     122       
     123       REAL(wp) ::  dqdt_precip  !:
    111124
    112125
Note: See TracChangeset for help on using the changeset viewer.