source: LMDZ6/trunk/libf/phylmd/clift.f90

Last change on this file was 5274, checked in by abarral, 3 hours ago

Replace yomcst.h by existing module

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 2.9 KB
RevLine 
[1992]1
[524]2! $Header$
[1992]3
4SUBROUTINE clift(p, t, rr, rs, plcl, dplcldt, dplcldq)
[5274]5  USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
6          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
7          , R_ecc, R_peri, R_incl                                      &
8          , RA, RG, R1SA                                         &
9          , RSIGMA                                                     &
10          , R, RMD, RMV, RD, RV, RCPD                    &
11          , RMO3, RMCO2, RMC, RMCH4, RMN2O, RMCFC11, RMCFC12        &
12          , RCPV, RCVD, RCVV, RKAPPA, RETV, eps_w                    &
13          , RCW, RCS                                                 &
14          , RLVTT, RLSTT, RLMLT, RTT, RATM                           &
15          , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS            &
16          , RALPD, RBETD, RGAMD
[2197]17IMPLICIT NONE
[1992]18  ! ***************************************************************
19  ! *                                                             *
20  ! * CLIFT : COMPUTE LIFTING CONDENSATION LEVEL AND ITS          *
21  ! *         DERIVATIVES RELATIVE TO T AND R                     *
22  ! *   (WITHIN 0.2% OF FORMULA OF BOLTON, MON. WEA. REV.,1980)   *
23  ! *                                                             *
24  ! * written by   : GRANDPEIX Jean-Yves, 17/11/98, 12.39.01      *
25  ! * modified by :                                               *
26  ! ***************************************************************
27  ! *
28  ! *Arguments :
29  ! *
30  ! * Input :  P = pressure of level from wich lifting is performed
31  ! *          T = temperature of level P
32  ! *          RR = vapour mixing ratio at level P
33  ! *          RS = vapour saturation mixing ratio at level P
34  ! *
35  ! * Output : PLCL = lifting condensation level
36  ! *          DPLCLDT = derivative of PLCL relative to T
37  ! *          DPLCLDQ = derivative of PLCL relative to R
38  ! *
39  ! cccccccccccccccccccccc
40  ! constantes coherentes avec le modele du Centre Europeen
41  ! RD = 1000.0 * 1.380658E-23 * 6.0221367E+23 / 28.9644
42  ! RV = 1000.0 * 1.380658E-23 * 6.0221367E+23 / 18.0153
43  ! CPD = 3.5 * RD
44  ! CPV = 4.0 * RV
45  ! CL = 4218.0
46  ! CI=2090.0
47  ! CPVMCL=CL-CPV
48  ! CLMCI=CL-CI
49  ! EPS=RD/RV
50  ! ALV0=2.5008E+06
51  ! ALF0=3.34E+05
52
53  ! on utilise les constantes thermo du Centre Europeen: (sb)
[5274]54 real :: p,t,rr,rs,plcl,dplcldt,dplcldq,cpd,cpv,cl,cpvmcl,eps,alv0,a,b
[2197]55  real :: rh,chi,alv
[1992]56
57  cpd = rcpd
58  cpv = rcpv
59  cl = rcw
60  cpvmcl = cl - cpv
61  eps = rd/rv
62  alv0 = rlvtt
63
64
65  ! Bolton formula coefficients :
66  a = 1669.0
67  b = 122.0
68
69  rh = rr/rs
70  chi = t/(a-b*rh-t)
71  plcl = p*(rh**chi)
72
73  alv = alv0 - cpvmcl*(t-273.15)
74
75  ! -- sb: correction:
76  ! DPLCLDQ = PLCL*CHI*( 1./RR - B*CHI/T/RS*ALOG(RH) )
77  dplcldq = plcl*chi*(1./rr+b*chi/t/rs*alog(rh))
78  ! sb --
79
80  dplcldt = plcl*chi*((a-b*rh*(1.+alv/rv/t))/t**2*chi*alog(rh)-alv/rv/t**2)
81
82
83  RETURN
84END SUBROUTINE clift
Note: See TracBrowser for help on using the repository browser.