source: LMDZ5/trunk/libf/phymar/PHY_Atm_CM_QSat.f90 @ 2089

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

Inclusion de la physique de MAR


Integration of MAR physics

File size: 5.7 KB
Line 
1      subroutine PHY_Atm_CM_QSat
2
3!------------------------------------------------------------------------------+
4!                                                         Mon 17-Jun-2013  MAR |
5!                                                                              |
6!     subroutine PHY_Atm_CM_QSat   computes specifics Humidities at Saturation |
7!            for Cloud Microphysical    Scheme used by MAR                     |
8!                                                                              |
9!     version 3.p.4.1 created by H. Gallee,               Sat 23-Mar-2013      |
10!           Last Modification by H. Gallee,               Mon 17-Jun-2013      |
11!                                                                              |
12!------------------------------------------------------------------------------+
13!                                                                              |
14!     INPUT :   Ta__DY:         Air Temperature                            [K] |
15!     ^^^^^     psa_DY: Model Pressure Thickness                         [kPa] |
16!                                                                              |
17!     OUTPUT :  qvswCM     : Saturation Specific Humidity  over Water  [kg/kg] |
18!     ^^^^^^    qvsiCM     : Saturation Specific Humidity  over Ice    [kg/kg] |
19!                                                                              |
20!     REFERENCE :  Dudhia (1989) JAS, (B1) and (B2) p.3103                     |
21!     ^^^^^^^^^                                                                |
22!------------------------------------------------------------------------------+
23
24      use Mod_Real
25      use Mod_PHY____dat
26      use Mod_PHY____grd
27      use Mod_PHY_DY_kkl
28      use Mod_PHY_CM_kkl
29
30
31
32
33! Local  Variables
34! ================
35
36      use Mod_Atm_CM_QSa
37
38
39      IMPLICIT NONE
40
41
42      integer i     ,j     ,ikl   ,k
43
44      real(kind=real8)                             ::  WatIce =  273.16e0
45      real(kind=real8)                             ::  ExpWat =    5.138e0
46      real(kind=real8)                             ::  ExpWa2 = 6827.e0
47      real(kind=real8)                             ::  ExpIce = 6150.e0
48      real(kind=real8)                             ::  pr__75 =   75.00        !                                      75 [hPa]
49      real(kind=real8)                             ::  qs__75 =    0.001       !                                 0.001 [kg/kg]
50
51      real(kind=real8)                             ::  Wphase
52      real(kind=real8)                             ::  qvSatI
53
54
55
56
57!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
58!                                                         !
59! ALLOCATION
60! ==========
61
62      IF (it_RUN.EQ.1 .OR. FlagDALLOC)               THEN !
63          allocate   ( pa_hPa(mzpp) )
64          allocate   ( pr_b75(mzpp) )
65          allocate   ( ei_sat(mzpp) )
66          allocate   ( ew_sat(mzpp) )
67      END IF
68!                                                         !
69!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
70
71
72!     ++++++++++++++++
73      DO ikl = 1,kcolp
74!     ++++++++++++++++
75
76
77
78! Temperature (K) and Pressure (hPa)
79! ==================================
80
81        DO k=1,mzpp
82          pa_hPa(k)   = (psa_DY(ikl) * sigma(k) + pt__DY) * 10.0d0
83
84
85! Pressure Discriminator
86! ----------------------
87
88          pr_b75(k)   = max(zer0,sign(un_1,pa_hPa(k)-pr__75))
89
90
91
92
93! Saturation Vapor Pressure over Ice
94! ==================================
95
96          ei_sat(k)    =                                               &
97     &    6.1070d0 * exp (ExpIce *(un_1/WatIce-un_1/Ta__DY(ikl,k) ) )
98!  ..     Dudhia (1989) JAS, (B1) and (B2) p.3103
99
100          qvSatI       = .622d0*ei_sat(k)                              &
101     &  /(pa_hPa(k)    - .378d0*ei_sat(k) )
102
103
104
105
106! Saturation Vapor Pressure over Water
107! ====================================
108
109          ew_sat(k)    =                                               &
110     &    6.1078d0 * exp (ExpWat *  log(WatIce     /Ta__DY(ikl,k) ) )  &
111     &             * exp (ExpWa2 *(un_1/WatIce-un_1/Ta__DY(ikl,k) ) )
112!  ..     Dudhia (1989) JAS, (B1) and (B2) p.3103
113!         See also Pielke (1984), p.234 and Stull (1988), p.276
114
115          qvswCM(ikl,k) = max(epsn  ,  .622d0*ew_sat(k)                &
116     &  /(pa_hPa(k) -                  .378d0*ew_sat(k)   ))
117!  ..     Saturation Vapor Specific Concentration over Water
118!         (even for temperatures less than freezing point)
119
120
121
122
123! Water Phase Discriminator
124! =========================
125
126          Wphase       = max(zer0,sign(un_1,Ta__DY(ikl,k)-WatIce))
127!  ..     Wphase       =     1    if        Tair     >    273.16
128!                            0    if        Tair     <    273.16
129
130
131
132
133! Saturation Vapor Specific Concentration over Ice
134! ================================================
135
136          qvsiCM(ikl,k) =                                              &
137     &       max(epsn    , qvswCM(ikl,k) *      Wphase                 &
138     &                   + qvSatI        *(un_1-Wphase))
139
140
141          qvswCM    (ikl,k) = pr_b75(k) *qvswCM(ikl,k) +(1.0-pr_b75(k)) *qs__75
142          qvsiCM    (ikl,k) = pr_b75(k) *qvsiCM(ikl,k) +(1.0-pr_b75(k)) *qs__75
143
144
145        END DO
146
147!     ++++++++++++++++++++++
148      END DO ! ikl = 1,kcolp
149!     ++++++++++++++++++++++
150
151
152
153!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
154!                                                         !
155! DE-ALLOCATION
156! =============
157
158      IF (FlagDALLOC)                                THEN !
159          deallocate ( pa_hPa )
160          deallocate ( pr_b75 )
161          deallocate ( ei_sat )
162          deallocate ( ew_sat )
163      END IF
164!                                                         !
165!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
166
167
168
169      return
170      end subroutine PHY_Atm_CM_QSat
Note: See TracBrowser for help on using the repository browser.