source: trunk/mars/libf/phymars/growthrate.F @ 120

Last change on this file since 120 was 120, checked in by emillour, 14 years ago

-Mars GCM:

set internal computations using double precision in growthrate.F and

watercloud.F (otherwise we sometimes end up with Nans).

add extra checks in newcondens.F to avoid possibility of out of bounds

evaluation of array masse()

EM

File size: 3.5 KB
Line 
1      subroutine growthrate(timestep,t,p,ph2o,psat,seq,r,Cste)
2
3      IMPLICIT NONE
4
5c=======================================================================
6c
7c     Determination of the water ice crystal growth rate
8c
9c=======================================================================
10
11c-----------------------------------------------------------------------
12c   declarations:
13c   -------------
14
15c
16c   arguments:
17c   ----------
18
19      REAL timestep
20      REAL t    ! temperature in the middle of the layer (K)
21      REAL p    ! pressure in the middle of the layer (K)
22      REAL*8 ph2o ! water vapor partial pressure (Pa)
23      REAL*8 psat ! water vapor saturation pressure (Pa)
24      REAL r    ! crystal radius before condensation (m)
25      REAL*8 seq  ! Equilibrium saturation ratio
26!      REAL dr   ! crystal radius variation (m)
27      REAL*8 Cste
28
29c   local:
30c   ------
31
32      REAL*8 molco2,molh2o
33      REAL*8 Mco2,Mh2o,rho_i,sigh2o
34      REAL*8 nav,rgp,kbz,pi,To
35
36c     Effective gas molecular radius (m)
37      data molco2/2.2d-10/   ! CO2
38c     Effective gas molecular radius (m)
39      data molh2o/1.2d-10/   ! H2O
40c     Molecular weight of CO2
41      data Mco2/44.d-3/            ! kg.mol-1
42c     Molecular weight of H2O
43      data Mh2o/18.d-3/            ! kg.mol-1
44c     surface tension of ice/vapor
45      data sigh2o/0.12/      ! N.m
46c     Ice density
47      data rho_i/917./        ! kg.m-3 also defined in initcld.f
48c     Avogadro number
49      data nav/6.023d23/
50c     Perfect gas constant
51      data rgp/8.3143/
52c     Boltzman constant
53      data kbz/1.381d-23/
54c     pi number
55      data pi/3.141592654/
56c     Reference temperature, T=273,15 K
57      data To/273.15/
58
59      REAL*8 k,Lv                 
60      REAL*8 knudsen           ! Knudsen number (gas mean free path/particle radius)
61      REAL*8 a,Dv,lambda       ! Intermediate computations for growth rate
62      REAL*8 Rk,Rd
63
64c-----------------------------------------------------------------------
65c      Ice particle growth rate by diffusion/impegement of water molecules
66c                r.dr/dt = (S-Seq) / (Seq*Rk+Rd)
67c        with r the crystal radius, Rk and Rd the resistances due to
68c        latent heat release and to vapor diffusion respectively
69c-----------------------------------------------------------------------
70
71c     - Equilibrium saturation accounting for KeLvin Effect
72       seq=exp(2*sigh2o*Mh2o/(rho_i*rgp*t*r))
73
74c     - Thermal conductibility of CO2
75      k  = (0.17913 * t - 13.9789) * 4.184e-4
76c     - Latent heat of h2o (J.kg-1)
77      Lv = (2834.3 - 0.28 * (t-To) - 0.004 * (t-To)**2 ) * 1.e+3
78
79c     - Constant to compute gas mean free path
80c     l= (T/P)*a, with a = (  0.707*8.31/(4*pi*molrad**2 * avogadro))
81      a = 0.707*rgp/(4 * pi* molco2**2  * nav)
82
83c     - Compute Dv, water vapor diffusion coefficient
84c       accounting for both kinetic and continuum regime of diffusion,
85c       the nature of which depending on the Knudsen number.
86
87      Dv = 1./3. * sqrt( 8*kbz*t/(pi*Mh2o/nav) )* kbz * t /
88     &   ( pi * p * (molco2+molh2o)**2 * sqrt(1.+Mh2o/Mco2) )
89
90      knudsen = t / p * a / r
91      lambda  = (1.333+0.71/knudsen) / (1.+1./knudsen)
92      Dv      = Dv / (1. + lambda * knudsen)
93
94c     - Compute Rk
95      Rk = Lv**2 * rho_i * Mh2o / (k*rgp*t**2.)
96c     - Compute Rd
97      Rd = rgp * t *rho_i / (Dv*psat*Mh2o)
98
99c     - Compute Cste=rdr/dt, then r(t+1)= sqrt(r(t)**2.+2.*Cste*dt)
100       Cste = 1. / (seq*Rk+Rd)
101c      Cste = (ph2o/psat-seq) / (seq*Rk+Rd)
102c      rf   = sqrt( max( r**2.+2.*Cste*timestep , 0. ) )
103c      dr   = rf-r
104
105      RETURN
106      END
107
Note: See TracBrowser for help on using the repository browser.