source: trunk/LMDZ.VENUS/libf/phyvenus/cloudvenus/thermo.F90 @ 1661

Last change on this file since 1661 was 1661, checked in by slebonnois, 8 years ago

SL: Cloud model for Venus. Not validated yet.

File size: 7.2 KB
Line 
1
2!  FUNCTION    FPLAIR     Mean free path of air molecules (m)
3!  FUNCTION    VISAIR     Dynamic viscosity of air
4!  FUNCTION    DFWVA      Diffusivity of water vapor in air
5!  FUNCTION    STSAS      Surface tension of H2SO4 solution/vapor
6!  FUNCTION    ROSAS      Density of liquid sulfuric acid solution
7!  FUNCTION    waterps    Saturation vapour pressure of pure water
8!  FUNCTION    CDTAIR     Thermal conduvtivity of air
9
10
11!*****************************************************************************
12FUNCTION FPLAIR(T,P)
13
14  ! Molecular mean free path of air molecules
15  ! Source: Seinfield's book (2006,p.399)
16
17  use free_param
18  use donnees
19
20  IMPLICIT NONE
21
22  REAL :: FPLAIR, T, P, VISAIR
23
24  FPLAIR=sqrt((PI*RGAS*T)/(2.0D0*MAIR))*(VISAIR(T)/P)
25 
26  RETURN
27
28END FUNCTION FPLAIR
29
30
31!*****************************************************************************
32FUNCTION VISAIR(T)
33
34  ! Dynamic viscosity of air.
35  ! Source: Jones 1942
36
37  ! Input:  TAIR:   Temperature (K)
38  ! Output: VISAIR: Dynamic viscosity of air  (kg/(m s))=(Pa s)
39 
40  use free_param
41  use donnees
42
43  IMPLICIT NONE
44 
45  REAL :: T, VISAIR
46  REAL :: AA, SS, T0
47
48  AA = (5.27D0-3.0D0)/(5.27D0 -1.0D0)
49  SS = -0.435D0
50  T0 = 200.0D0
51
52  VISAIR=1015.0D0*((T/T0)**(0.5D0))*(T0**(AA)+SS)/(T**(AA)+SS)
53  VISAIR=VISAIR*1.D-8
54 
55  RETURN
56
57END FUNCTION VISAIR
58
59
60!*****************************************************************************
61FUNCTION DFWVA(T,P)
62
63  !     Diffusivity of water vapor in air.
64  !     Source: Prupacher & Klett:Microphysics of clouds and precipitation,
65  !                               (1980), 13-3, p. 413
66  !     The relation D = E0 (T/T0)**n (P0/P); n=1.94 has been used.
67 
68  !     Input:  TAIR: Temperature (K);  Range:  [180,273]
69  !             PAIR: Pressure (Pa)
70  !     Output: Diffusivity of water vapor in air  (m**2/sec)
71 
72  use free_param
73  use donnees
74
75  IMPLICIT NONE
76
77  REAL :: E0, D1, P0, T0, T, P, DFWVA
78
79  PARAMETER(E0=0.211D-4,P0=1.01325D+5,T0=273.15D0,D1=E0*P0)
80 
81  DFWVA=D1*((T/T0)**1.94D0)/P
82 
83  RETURN
84
85END FUNCTION DFWVA
86
87
88!*****************************************************************************
89FUNCTION STSAS(T,xmass)
90  !     Input:  T: Temperature (K)
91  !             xmass: Mass fraction of H2SO4  [0;1]
92  !     Output: Surface tension of sulfuric acid solution (N/m)
93
94! about 230-323 K , x=0,...,1
95!(valid down to the solid phase limit temp, which depends on molefraction)
96
97  use donnees
98      IMPLICIT NONE
99      REAL :: STSAS
100      REAL, INTENT(IN):: xmass, T
101      REAL :: a, b, T1, Tc, xmole
102
103       IF (T .LT. 305.15) THEN
104
105!low temperature surface tension
106! Hanna Vehkam‰ki and Markku Kulmala and Ismo Napari
107! and Kari E. J. Lehtinen and Claudia Timmreck and Madis Noppel and Ari Laaksonen, 2002,
108! An improved parameterization for sulfuric acid/water nucleation rates for tropospheric
109!and stratospheric conditions, () J. Geophys. Res., 107, pp. 4622-4631
110
111          a= 0.11864 + xmass* (-0.11651    &   
112                     + xmass* ( 0.76852    &
113                     + xmass* (-2.40909    &
114                     + xmass*  (2.95434    &
115                     + xmass* (-1.25852)))))
116                     
117          b= -0.00015709 + xmass* (0.00040102   &
118                         + xmass*(-0.00239950   &
119                         + xmass* (0.007611235  &
120                         + xmass*(-0.00937386   &
121                         + xmass*0.00389722))))
122          STSAS=a+T*b
123
124      ELSE
125
126      xmole = (xmass/MSA)*(1./((xmass/MSA)+(1.-xmass)/MWV))
127     
128! high temperature surface tension
129!H. Vehkam‰ki and M. Kulmala and K.E. J. lehtinen, 2003,
130!Modelling binary homogeneous nucleation of water-sulfuric acid vapours:
131! parameterisation for high temperature emissions, () Environ. Sci. Technol., 37, 3392-3398
132
133      Tc=    647.15*(1.0-xmole)*(1.0-xmole)   &
134         +   900.0 *   xmole   *  xmole       &
135         + 3156.186*   xmole   *(1-xmole)          !critical temperature
136      T1=1.0-T/Tc
137
138      a= 0.2358 + xmole*(-0.529     &
139                + xmole* (4.073     &
140                + xmole*(-12.6707   &
141                + xmole* (15.3552   &
142                + xmole*(-6.3138)))))
143               
144      b= -0.14738 + xmole* (0.6253   &
145                  + xmole*(-5.4808   &
146                  + xmole*(17.2366   &
147                  + xmole*(-21.0487  &
148                  + xmole*(8.719)))))
149      STSAS=(a+b*T1)*T1**(1.256)
150
151      END IF
152      RETURN
153
154END FUNCTION STSAS
155
156
157!*****************************************************************************
158FUNCTION ROSAS(T,xmass)
159
160!
161! calculates the density of the liquid in kg/m^3
162! xmass=mass fraction of h2so4, T in kelvins
163! Hanna Vehkam‰ki and Markku Kulmala and Ismo Napari
164! and Kari E. J. Lehtinen and Claudia Timmreck and Madis Noppel and Ari Laaksonen, 2002,
165! An improved parameterization for sulfuric acid/water nucleation rates for tropospheric
166!and stratospheric conditions, () J. Geophys. Res., 107, pp. 4622-4631
167
168! about 220-373 K , x=0,...,1
169!(valid down to the solid phase limit temp, which depends on molefraction)
170
171      IMPLICIT NONE
172      REAL :: ROSAS
173      REAL, INTENT(IN) :: T, xmass
174      REAL ::  a,b,c
175
176
177      a= 0.7681724 + xmass* (2.1847140         &
178                   + xmass* (7.1630022         &
179                   + xmass* (-44.31447         &
180                   + xmass* (88.75606          &
181                   + xmass*(-75.73729          &
182                   + xmass*  23.43228 )))))
183
184      b= 1.808225e-3 + xmass* (-9.294656e-3       &
185                     + xmass* (-0.03742148        &
186                     + xmass* (0.2565321          &
187                     + xmass* (-0.5362872         &
188                     + xmass* (0.4857736          &
189                     + xmass* (-0.1629592))))))
190     
191      c= -3.478524e-6 + xmass* (1.335867e-5      &
192                      + xmass* (5.195706e-5      &
193                      + xmass*(-3.717636e-4      &
194                      + xmass* (7.990811e-4      &
195                      + xmass*(-7.458060e-4      &
196                      + xmass*  2.58139e-4)))))
197     
198      ROSAS= a+T*(b+c*T) ! g/cm^3
199      ROSAS= ROSAS*1.0e3 !kg/m^3
200     
201      RETURN
202END FUNCTION ROSAS
203
204
205!****************************************************************
206FUNCTION waterps(t)
207
208  !     Saturation vapour pressure of pure water in Pa
209  !     temperature t in K
210
211  !     for 0 to 100C: Wexler 1976
212  !     for <0C (validity range 123-332K): Murphy and Koop 2005
213
214  use free_param
215  use donnees
216
217  IMPLICIT NONE
218
219  REAL:: waterps, t,w
220
221  if(t .ge. 273.15D0) then
222     waterps=exp(-2991.2729D0*(t**(-2.))-6017.0128D0/t+18.87643854D0 &
223          &        -0.028354721D0*t+0.17838301D-4*t**2.-0.84150417D-9*t**3. &
224          &        +0.44412543D-12*t**4.+2.858487D0*LOG(t))
225  else if(t .lt. 273.15D0) then
226     waterps=exp(54.842763D0-6763.22D0/t-4.210D0*LOG(t)+0.000367D0*t &
227          &        + tanh(0.0415D0*(t- 218.8D0))*(53.878D0- 1331.22D0/t &
228          &        - 9.44523D0*LOG(t) + 0.014025D0*t))
229  else
230     stop 'no good temperatures in waterps!'
231  endif
232
233END FUNCTION waterps
234
235
236!****************************************************************
237FUNCTION CDTAIR(T)
238
239  !     Thermal conduvtivity of air
240  !     Source: Prupacher & Klett:Microphysics of clouds and precipitation,
241  !                               (1980), p 418, 13-16
242  !     Formula used:             CDTAIR=4.381276E-3+7.117560E-5*TAIR
243 
244  !     Input:  TAIR:     Air temperature (K)
245  !     Output:           Thermal conductivity of air (J/(m sec K))
246 
247  use free_param
248  use donnees
249 
250  IMPLICIT NONE
251
252  REAL :: CDTAIR, T
253
254  CDTAIR=4.381276D-3+7.117560D-5*T
255
256  RETURN
257
258END FUNCTION CDTAIR
259
Note: See TracBrowser for help on using the repository browser.