source: palm/trunk/SOURCE/compute_vpt.f90 @ 4784

Last change on this file since 4784 was 4742, checked in by schwenkel, 3 years ago

Implement snow and graupel (bulk microphysics)

  • Property svn:keywords set to Id
File size: 3.4 KB
Line 
1!> @file compute_vpt.f90
2!--------------------------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General
6! Public License as published by the Free Software Foundation, either version 3 of the License, or
7! (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
11! Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with PALM. If not, see
14! <http://www.gnu.org/licenses/>.
15!
16! Copyright 1997-2020 Leibniz Universitaet Hannover
17!--------------------------------------------------------------------------------------------------!
18!
19! Current revisions:
20! -----------------
21!
22!
23! Former revisions:
24! -----------------
25! $Id: compute_vpt.f90 4742 2020-10-14 15:11:02Z suehring $
26! Implement snow and graupel (bulk microphysics)
27!
28! 4559 2020-06-11 08:51:48Z raasch
29! file re-formatted to follow the PALM coding standard
30!
31! 4521 2020-05-06 11:39:49Z schwenkel
32! Rename variable
33!
34! 4502 2020-04-17 16:14:16Z schwenkel
35! Implementation of ice microphysics
36!
37! 4360 2020-01-07 11:25:50Z suehring
38! Corrected "Former revisions" section
39!
40! 3655 2019-01-07 16:51:22Z knoop
41! Modularization of all bulk cloud physics code components
42!
43! Revision 1.1  2000/04/13 14:40:53  schroeter
44! Initial revision
45!
46!
47! Description:
48! -------------
49!> Computation of the virtual potential temperature
50!--------------------------------------------------------------------------------------------------!
51 SUBROUTINE compute_vpt
52 
53
54    USE arrays_3d,                                                                                 &
55        ONLY:  d_exner, pt, q, qf, ql, vpt
56
57    USE basic_constants_and_equations_mod,                                                         &
58        ONLY:  ls_d_cp, lv_d_cp
59
60    USE control_parameters,                                                                        &
61        ONLY:  cloud_droplets
62
63    USE indices,                                                                                   &
64        ONLY:  nzb, nzt
65
66    USE kinds
67
68    USE bulk_cloud_model_mod,                                                                      &
69        ONLY:  bulk_cloud_model, microphysics_ice_phase
70
71    IMPLICIT NONE
72
73    INTEGER(iwp) :: k   !<
74
75    IF ( .NOT. bulk_cloud_model  .AND.  .NOT. cloud_droplets )  THEN
76       vpt = pt * ( 1.0_wp + 0.61_wp * q )
77    ELSEIF ( bulk_cloud_model  .AND.  .NOT. microphysics_ice_phase )  THEN
78       DO  k = nzb, nzt+1
79              vpt(k,:,:) = ( pt(k,:,:) + d_exner(k) * lv_d_cp * ql(k,:,:) ) *                      &
80                           ( 1.0_wp + 0.61_wp * q(k,:,:) - 1.61_wp *  ql(k,:,:)  )
81       ENDDO
82    ELSEIF ( bulk_cloud_model  .AND.  microphysics_ice_phase )  THEN
83       DO  k = nzb, nzt+1
84          vpt(k,:,:) = ( pt(k,:,:) + d_exner(k) * lv_d_cp * ql(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,:,:) ) )
87       ENDDO
88    ELSE
89       vpt = pt * ( 1.0_wp + 0.61_wp * q - ql ) 
90    ENDIF
91
92 END SUBROUTINE compute_vpt
Note: See TracBrowser for help on using the repository browser.