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

Last change on this file since 4565 was 4559, checked in by raasch, 4 years ago

files re-formatted to follow the PALM coding standard

  • Property svn:keywords set to Id
File size: 3.3 KB
RevLine 
[1682]1!> @file compute_vpt.f90
[4559]2!--------------------------------------------------------------------------------------------------!
[2696]3! This file is part of the PALM model system.
[1036]4!
[4559]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.
[1036]8!
[4559]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.
[1036]12!
[4559]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/>.
[1036]15!
[4360]16! Copyright 1997-2020 Leibniz Universitaet Hannover
[4559]17!--------------------------------------------------------------------------------------------------!
[1036]18!
[484]19! Current revisions:
[1]20! -----------------
[1354]21!
[2001]22!
[1321]23! Former revisions:
24! -----------------
25! $Id: compute_vpt.f90 4559 2020-06-11 08:51:48Z oliver.maas $
[4559]26! file re-formatted to follow the PALM coding standard
27!
28! 4521 2020-05-06 11:39:49Z schwenkel
[4521]29! Rename variable
30!
31! 4502 2020-04-17 16:14:16Z schwenkel
[4502]32! Implementation of ice microphysics
33!
34! 4360 2020-01-07 11:25:50Z suehring
[4182]35! Corrected "Former revisions" section
36!
37! 3655 2019-01-07 16:51:22Z knoop
[3274]38! Modularization of all bulk cloud physics code components
[1321]39!
[4182]40! Revision 1.1  2000/04/13 14:40:53  schroeter
41! Initial revision
42!
43!
[1]44! Description:
45! -------------
[1682]46!> Computation of the virtual potential temperature
[4559]47!--------------------------------------------------------------------------------------------------!
[1682]48 SUBROUTINE compute_vpt
49 
[1]50
[4559]51    USE arrays_3d,                                                                                 &
52        ONLY:  d_exner, pt, q, qi, ql, vpt
[3274]53
[4559]54    USE basic_constants_and_equations_mod,                                                         &
55        ONLY:  ls_d_cp, lv_d_cp
[3274]56
[4559]57    USE control_parameters,                                                                        &
[3274]58        ONLY:  cloud_droplets
59
[4559]60    USE indices,                                                                                   &
[1320]61        ONLY:  nzb, nzt
[3274]62
[1320]63    USE kinds
[1]64
[4559]65    USE bulk_cloud_model_mod,                                                                      &
[4521]66        ONLY:  bulk_cloud_model, microphysics_ice_phase
[3274]67
[1]68    IMPLICIT NONE
69
[1682]70    INTEGER(iwp) :: k   !<
[1]71
[3274]72    IF ( .NOT. bulk_cloud_model  .AND.  .NOT. cloud_droplets )  THEN
[1353]73       vpt = pt * ( 1.0_wp + 0.61_wp * q )
[4521]74    ELSEIF ( bulk_cloud_model  .AND.  .NOT. microphysics_ice_phase )  THEN
[1]75       DO  k = nzb, nzt+1
[4559]76              vpt(k,:,:) = ( pt(k,:,:) + d_exner(k) * lv_d_cp * ql(k,:,:) ) *                      &
77                           ( 1.0_wp + 0.61_wp * q(k,:,:) - 1.61_wp *  ql(k,:,:)  )
[1]78       ENDDO
[4559]79    ELSEIF ( bulk_cloud_model  .AND.  microphysics_ice_phase )  THEN
[4502]80       DO  k = nzb, nzt+1
[4559]81          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,:,:) ) )
[4502]84       ENDDO
[799]85    ELSE
[1353]86       vpt = pt * ( 1.0_wp + 0.61_wp * q - ql ) 
[1]87    ENDIF
88
[4559]89 END SUBROUTINE compute_vpt
Note: See TracBrowser for help on using the repository browser.