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/compute_vpt.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:
     
    3238! Bugfix: wrong factor in calculation of vpt in case of cloud droplets
    3339!
    34 ! 799 2011-12-21 17:48:03Z franke
    35 ! Bugfix: ql is now included in calculation of vpt in case of
    36 !         cloud droplets
    37 !
    38 ! RCS Log replace by Id keyword, revision history cleaned up
    39 !
    40 ! Revision 1.5  2001/03/30 06:58:52  raasch
    41 ! Translation of remaining German identifiers (variables, subroutines, etc.)
    42 !
    4340! Revision 1.1  2000/04/13 14:40:53  schroeter
    4441! Initial revision
     
    4845! -------------
    4946! Computation of the virtual potential temperature
    50 !-------------------------------------------------------------------------------!
     47!------------------------------------------------------------------------------!
    5148
    52     USE arrays_3d
    53     USE indices
    54     USE cloud_parameters
    55     USE control_parameters
     49    USE arrays_3d,                                                             &
     50        ONLY:  pt, q, ql, vpt
     51       
     52    USE indices,                                                               &
     53        ONLY:  nzb, nzt
     54       
     55    USE cloud_parameters,                                                      &
     56        ONLY:  l_d_cp, pt_d_t
     57       
     58    USE control_parameters,                                                    &
     59        ONLY:  cloud_droplets, cloud_physics
     60       
     61    USE kinds
    5662
    5763    IMPLICIT NONE
    5864
    59     INTEGER :: k
     65    INTEGER(iwp) :: k   !:
    6066
    61     IF ( .NOT. cloud_physics .AND. .NOT. cloud_droplets ) THEN
     67    IF ( .NOT. cloud_physics  .AND.  .NOT. cloud_droplets ) THEN
    6268       vpt = pt * ( 1.0 + 0.61 * q )
    63     ELSE IF (cloud_physics) THEN
     69    ELSE IF (cloud_physics)  THEN
    6470       DO  k = nzb, nzt+1
    65           vpt(k,:,:) = ( pt(k,:,:) + pt_d_t(k) * l_d_cp * ql(k,:,:) ) * &
     71          vpt(k,:,:) = ( pt(k,:,:) + pt_d_t(k) * l_d_cp * ql(k,:,:) ) *        &
    6672                       ( 1.0 + 0.61 * q(k,:,:) - 1.61 * ql(k,:,:) )
    6773       ENDDO
Note: See TracChangeset for help on using the changeset viewer.