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

Last change on this file since 5301 was 5285, checked in by abarral, 4 days ago

As discussed internally, remove generic ONLY: ... for new _mod_h modules

  • 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.1 KB
Line 
1
2! $Header$
3
4SUBROUTINE clift(p, t, rr, rs, plcl, dplcldt, dplcldq)
5  USE yomcst_mod_h
6IMPLICIT NONE
7  ! ***************************************************************
8  ! *                                                             *
9  ! * CLIFT : COMPUTE LIFTING CONDENSATION LEVEL AND ITS          *
10  ! *         DERIVATIVES RELATIVE TO T AND R                     *
11  ! *   (WITHIN 0.2% OF FORMULA OF BOLTON, MON. WEA. REV.,1980)   *
12  ! *                                                             *
13  ! * written by   : GRANDPEIX Jean-Yves, 17/11/98, 12.39.01      *
14  ! * modified by :                                               *
15  ! ***************************************************************
16  ! *
17  ! *Arguments :
18  ! *
19  ! * Input :  P = pressure of level from wich lifting is performed
20  ! *          T = temperature of level P
21  ! *          RR = vapour mixing ratio at level P
22  ! *          RS = vapour saturation mixing ratio at level P
23  ! *
24  ! * Output : PLCL = lifting condensation level
25  ! *          DPLCLDT = derivative of PLCL relative to T
26  ! *          DPLCLDQ = derivative of PLCL relative to R
27  ! *
28  ! cccccccccccccccccccccc
29  ! constantes coherentes avec le modele du Centre Europeen
30  ! RD = 1000.0 * 1.380658E-23 * 6.0221367E+23 / 28.9644
31  ! RV = 1000.0 * 1.380658E-23 * 6.0221367E+23 / 18.0153
32  ! CPD = 3.5 * RD
33  ! CPV = 4.0 * RV
34  ! CL = 4218.0
35  ! CI=2090.0
36  ! CPVMCL=CL-CPV
37  ! CLMCI=CL-CI
38  ! EPS=RD/RV
39  ! ALV0=2.5008E+06
40  ! ALF0=3.34E+05
41
42  ! on utilise les constantes thermo du Centre Europeen: (sb)
43 real :: p,t,rr,rs,plcl,dplcldt,dplcldq,cpd,cpv,cl,cpvmcl,eps,alv0,a,b
44  real :: rh,chi,alv
45
46  cpd = rcpd
47  cpv = rcpv
48  cl = rcw
49  cpvmcl = cl - cpv
50  eps = rd/rv
51  alv0 = rlvtt
52
53
54  ! Bolton formula coefficients :
55  a = 1669.0
56  b = 122.0
57
58  rh = rr/rs
59  chi = t/(a-b*rh-t)
60  plcl = p*(rh**chi)
61
62  alv = alv0 - cpvmcl*(t-273.15)
63
64  ! -- sb: correction:
65  ! DPLCLDQ = PLCL*CHI*( 1./RR - B*CHI/T/RS*ALOG(RH) )
66  dplcldq = plcl*chi*(1./rr+b*chi/t/rs*alog(rh))
67  ! sb --
68
69  dplcldt = plcl*chi*((a-b*rh*(1.+alv/rv/t))/t**2*chi*alog(rh)-alv/rv/t**2)
70
71
72  RETURN
73END SUBROUTINE clift
Note: See TracBrowser for help on using the repository browser.