Ignore:
Timestamp:
Oct 14, 2020 3:11:02 PM (4 years ago)
Author:
schwenkel
Message:

Implement snow and graupel (bulk microphysics)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/compute_vpt.f90

    r4559 r4742  
    1919! Current revisions:
    2020! -----------------
    21 ! 
    22 ! 
     21!
     22!
    2323! Former revisions:
    2424! -----------------
    2525! $Id$
     26! Implement snow and graupel (bulk microphysics)
     27!
     28! 4559 2020-06-11 08:51:48Z raasch
    2629! file re-formatted to follow the PALM coding standard
    2730!
     
    5053
    5154    USE arrays_3d,                                                                                 &
    52         ONLY:  d_exner, pt, q, qi, ql, vpt
     55        ONLY:  d_exner, pt, q, qf, ql, vpt
    5356
    5457    USE basic_constants_and_equations_mod,                                                         &
     
    8083       DO  k = nzb, nzt+1
    8184          vpt(k,:,:) = ( pt(k,:,:) + d_exner(k) * lv_d_cp * ql(k,:,:)   +                          &
    82                                      d_exner(k) * ls_d_cp * qi(k,:,:) ) *                          &
    83                        ( 1.0_wp + 0.61_wp * q(k,:,:) - 1.61_wp * ( ql(k,:,:) + qi(k,:,:) ) )
     85                                     d_exner(k) * ls_d_cp * qf(k,:,:) ) *                          &
     86                       ( 1.0_wp + 0.61_wp * q(k,:,:) - 1.61_wp * ( ql(k,:,:) + qf(k,:,:) ) )
    8487       ENDDO
    8588    ELSE
Note: See TracChangeset for help on using the changeset viewer.