source: LMDZ6/trunk/libf/phymar/qv_sat.f90 @ 3830

Last change on this file since 3830 was 2089, checked in by Laurent Fairhead, 10 years ago

Inclusion de la physique de MAR


Integration of MAR physics

File size: 2.6 KB
Line 
1      function qv_sat(TTK,ss,pstar,pt,lsf)
2
3!--------------------------------------------------------------------------+
4!   MAR PHYSICS                                         Mc 30-05-2007  MAR |
5!     Function qv_sat computes the Saturation Specific Humidity    (kg/kg) |
6!                                                                          |
7!--------------------------------------------------------------------------+
8!                                                                          |
9!     INPUT :   TTK            : Air Temperature                       (K) |
10!     ^^^^^^^   pstar * ss + pt: Pressure of sigma level ss          (kPa) |
11!                                                                          |
12!     OUTPUT :  e__sat: Saturation Vapor    Pressure                 (hPa) |
13!     ^^^^^^^   qv_sat: Saturation Specific Humidity               (kg/kg) |
14!                                                                          |
15!--------------------------------------------------------------------------+
16
17
18      IMPLICIT NONE
19
20
21! Global Variables
22! ================
23
24      real     ::  qv_sat
25      real     ::  TTK   
26      real     ::  ss   
27      real     ::  pstar
28      real     ::  pt   
29      integer  ::  lsf
30
31
32! Local  Variables
33! ================
34
35      real     ::  pr   
36      real     ::  e__sat
37      real     ::  r273p1 = 273.16
38      real     ::  zer0   =   1.00
39      real     ::  un_1   =   1.00
40      real     ::  eps9   =   1.e-9
41      real     ::  pr__75 =  75.00
42      real     ::  pr_b75
43
44
45! Saturation Vapor    Pressure
46! ============================
47
48
49      pr   = 10.d0 *(pstar *ss + pt)                                    !  pressure (hPa)
50
51      IF (TTK.ge.273.16d0.or.lsf.eq.0)                              THEN
52
53        e__sat =  6.1078d0 * exp (5.138d0*log(  r273p1     /TTK))      &!  saturated vapor pressure with respect to water
54     &                     * exp (6827.d0*(un_1/r273p1-un_1/TTK))       !  Dudhia (1989) JAS, (B1) and (B2) p.3103
55                                                                        !  See also Pielke (1984), p.234 and Stull (1988), p.276
56
57      ELSE
58        e__sat =  6.107d0  * exp (6150.d0*(un_1/r273p1-un_1/TTK))       !  saturated vapor pressure with respect to ice
59                                                                        !  Dudhia (1989) JAS, (B1) and (B2) p.3103
60      END IF
61
62        pr_b75 = max(zer0  ,           sign(un_1,pr - pr__75))
63
64
65
66!       ******
67        qv_sat = pr_b75*max(eps9  , .622d0*e__sat/(pr-.378d0*e__sat))  &!
68     &    + (1.0-pr_b75)  * 1.e-3                                       !
69!       ******
70
71
72
73      return
74      end     
Note: See TracBrowser for help on using the repository browser.