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/calc_liquid_water_content.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! revision history before 2012 removed,
     26! comment fields (!:) to be used for variable explanations added to
     27! all variable declaration statements
    2328!
    2429! Former revisions:
     
    3843! code put under GPL (PALM 3.9)
    3944!
    40 ! 667 2010-12-23 12:06:00Z suehring/gyschka
    41 ! nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng
    42 !
    43 ! 95 2007-06-02 16:48:38Z raasch
    44 ! hydro_press renamed hyp
    45 !
    46 ! 19 2007-02-23 04:53:48Z raasch
    47 ! Old comment removed
    48 !
    49 ! RCS Log replace by Id keyword, revision history cleaned up
    50 !
    51 ! Revision 1.5  2005/03/26 15:22:06  raasch
    52 ! Arguments for non-cyclic boundary conditions added to argument list of
    53 ! routine exchange_horiz,
    54 ! ql calculated for the ghost points, exchange of ghost points removed
    55 !
    5645! Revision 1.1  2000/04/13 14:50:45  schroeter
    5746! Initial revision
     
    6756
    6857
    69     USE arrays_3d
    70     USE cloud_parameters
    71     USE constants
    72     USE control_parameters
    73     USE grid_variables
    74     USE indices
     58    USE arrays_3d,                                                             &
     59        ONLY:  hyp, pt, q, qc, ql, qr
     60
     61    USE cloud_parameters,                                                      &
     62        ONLY:  l_d_cp, l_d_r, t_d_pt
     63
     64    USE control_parameters,                                                    &
     65        ONLY:  icloud_scheme, precipitation
     66
     67    USE indices,                                                               &
     68        ONLY:  nxlg, nxrg, nyng, nysg, nzb_s_inner, nzt
     69
     70    USE kinds
     71
    7572    USE pegrid
     73
    7674
    7775    IMPLICIT NONE
    7876
    79     INTEGER :: i, j, k
     77    INTEGER(iwp) ::  i !:
     78    INTEGER(iwp) ::  j !:
     79    INTEGER(iwp) ::  k !:
    8080
    81     REAL :: alpha, e_s, q_s, t_l
     81    REAL(wp) ::  alpha !:
     82    REAL(wp) ::  e_s   !:
     83    REAL(wp) ::  q_s   !:
     84    REAL(wp) ::  t_l   !:
    8285
    8386    DO  i = nxlg, nxrg
     
    9194!
    9295!--          Compute saturation water vapor pressure at t_l
    93              e_s = 610.78 * EXP( 17.269 * ( t_l - 273.16 ) / &
     96             e_s = 610.78 * EXP( 17.269 * ( t_l - 273.16 ) /                   &
    9497                                          ( t_l - 35.86 ) )
    9598
Note: See TracChangeset for help on using the changeset viewer.