source: trunk/LMDZ.VENUS/libf/phyvenus/cloudvenus/flux.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: 2.2 KB
Line 
1SUBROUTINE FLUX(TAIR,PAIR,dt,sig,r,M3g,dM0,dM3)
2
3  !*  Masses flux = Condensation/Evaporation + Thermodynamical equilibrium
4  !*
5  !*  Condensation/Evaporation:
6  !*    Sulfuric acid drive this process (James 1997): most present in droplets
7  !*    more or less 95%
8  !*
9  !*  Thermodynamical equilibrium:
10  !*    Only water flux here (James 1997) => compare to acid vapor, water
11  !*    vapor is most present in the atmosphere
12  !*
13  !*  ONLY FOR ONE MODE HERE
14
15  use free_param
16  use donnees
17
18  IMPLICIT NONE
19
20  real, intent(in), dimension(3) :: M3g ! Third moment of the mode
21  real, intent(in) :: TAIR, PAIR, dt    ! Temp, timestep, pressure
22  real, intent(in) :: r, sig      ! Mean radius and variance of the mode
23  real, intent(out) :: dM3, dM0   ! Tendancy
24
25  real :: RDSA, RCSA               ! Resistance
26  real :: A , B, cste, a1, a2, a3  ! Calculus cstes
27  real :: alpha_k   ! Function
28  real :: MSAD      ! Mass of sulfuric acid in the droplet, in kg
29  real :: mk3       ! Tendancy
30  real :: gamma
31
32
33  ! ----- EQUILIBRIUM -----
34  CALL WSA_ROSA_NEW(TAIR,PAIR,r,WSAEQ,MSAD) ! Calculation of WSA
35
36  ! ----- CONDENSATION / EVAPORATION -----
37  IF (WSAEQ .gt. 0) THEN
38     ! Resistance due to the VAPOR diffusion (s/m2)
39     ! Here, we supposed a Dirac function for the calculation of D (Kn(r)
40     RDSA = (RHOSA*RGAS*TAIR) / (D*MSA*RHOsasat)
41     ! Resistance due to the HEAT diffusion (s/m2)
42     RCSA = (LSA*RHOSA)/(KAIR*TAIR) * ((LSA*MSA)/(RGAS*TAIR)-1.0D0)
43
44     A = 2.0D0*ST*MSA / (RHOSA*RGAS*TAIR) !m
45     B = exp(A/r) 
46     cste = 3.0D0/(RCSA+RDSA)
47
48     a1 = SH2SO4-B-A*B/r-(r**2)*B*A/2.0D0*(2.0D0*r+A)/(r**4)
49     a2 = A*B/(r**3) * (A+3.0D0*r)                  !m-1
50     a3 = (-1.0D0)*A*B * (2.0D0*r+A)/(2.0D0*r**4)   !m-2
51
52     gamma = (a1 * r**(-2) * alpha_k(1,sig)/alpha_k(3,sig) + &
53          &  a2 * r**(-1) * alpha_k(2,sig)/alpha_k(3,sig) + &
54          &  a3) * cste
55
56     mk3 = (1.D0/dt)*((WSA/WSAEQ) - 1.D0)*dt
57     mk3 = mk3 + (gamma/WSAEQ)
58     mk3 = 1.D0 - mk3
59     mk3 = (1.D0/mk3) * (M3g(1)+M3g(2)+M3g(3))
60
61     ! ----- TOTAL FLUX -----
62     !  dm < 0: evaporation and dm > 0: condensation
63     dM3 = mk3 - (M3g(1) + M3g(2) + M3g(3)) !m3 s
64     dM0 = dM3 / (r**3*alpha_k(3,sig))
65  ELSE
66     dM3 = 0.D0
67     dM0 = 0.D0
68  END IF
69
70  WSA = WSAEQ
71
72  RETURN
73END SUBROUTINE FLUX
Note: See TracBrowser for help on using the repository browser.