source: trunk/LMDZ.VENUS/libf/phyvenus/cloudvenus/donnees.F90 @ 3556

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

SL: update of the cloud model after first debug

File size: 6.7 KB
Line 
1MODULE donnees
2
3  implicit none
4
5  real, parameter :: ZERO = 2.220446049250313E-016
6  real, parameter :: PI = 3.1415926536D0
7  real, save :: E          ! Constant for microphys. processes
8
9
10  ! THERMO
11  real, parameter :: kbz = 1.3806488D-23 !m2.kg.s-2.K-2 Boltzmann constant
12  real, parameter :: RGAS = 8.31441D0    !J/(mole K)    Gas constant
13  real, parameter :: LSA = 6.322D5       !J/kg     Latent heat of evap of SA
14  real, parameter :: MAIR = 43.45D-3     !kg/mole  Molecular mass of venus air
15  real, parameter :: MWV = 18.0153D-3    !kg/mole  Molecular mass of water
16  real, parameter :: CSA = 0.4430057096D0!=MAIR/MSA   
17
18  real, save :: PPSA, PPWV ! Partial pressure of SA and water
19  real, save :: RH     ! Relative Humidity
20  real, save :: KAIR   ! Thermal conductivity of air (J/m sec K)
21  real, save :: KN     ! Knudsen number
22  real, save :: D      ! Molecular diffusivity of the air (m2/s)
23  real, save :: akn    ! Approx slip-flow correction coef
24!  real, parameter :: akn = 1.591D0 ! Approx slip-flow correction coeff
25
26
27  ! SEDIMENTATION and PRODUCTION
28  !> Fractal dimension of fractal aerosols.
29  REAL, SAVE :: df = 3.D0  ! 3 = sphere
30  !> Monomer radius (m).
31  REAL, SAVE :: rmono = 6.66D-8   
32  REAL, SAVE :: rpla = 6051800.D0 !m Venus radius
33  !> Planet acceleration due to gravity constant (ground) (\(m.s^{-2}\)).
34  REAL, SAVE :: g0 = 6.673D-11*(4.867D24/(6051800.D0)**2)
35!!$  !> Air molecules mean radius (m).   !SG   Y|°O°|Y
36  REAL, SAVE :: air_rad  = 1.75D-10
37
38
39  ! MODES  (H2SO4-H2O)
40  real, save :: redge  ! Virtual limits between the two modes
41  real, save :: r1, r2 ! Mean raidus of the distribution (m)
42  real, save :: N1, N2 ! Total number concentration (#/m3)
43  real, save :: NTOT   ! Total number of droplets (mode 1 and 2)
44
45
46  ! DROPLET AND GAS
47  real, save :: WSA, WSAEQ, SH2SO4, RHOSA, RHOsasat
48
49  ! Heterogeneous nucleation parameter (Franck's thesis, p.34)
50  real, parameter :: desorpco2 = 6.D-20  !J   Absorp./desorp. of 1 h2o molecule at the CCN surface
51  real, parameter :: surfdifco2 = 6.D-21 !J   Activation energy for surface diffusion
52  real, parameter :: nusco2 = 1.D+13     !s-1 Jump frequency
53
54  ! CONSERVATION
55  real, save :: CHECKSA
56  real, save :: CHECKWV
57
58  ! H2SO4
59  ! vo1h2so4 = masse 1 moléc. AS en kg / densité AS en kg/m3
60  ! vo1h2so4 = m_point/rho = 1.628656574D-25/1.8302D3
61  real, parameter :: vo1h2so4 = 8.898790154D-29 !m3
62  real, parameter :: m0h2so4 = 1.628640074D-25  !kg       Wettability
63  real, parameter :: MSA = 98.08D-3             !kg/mole  Molecular mass of SA
64  real, save :: ST         ! Surface tension of sulfuric acid solution/vapor (N/m)
65
66  real, save :: sigh2so4 ! tension superficielle de H2SO4
67  real, save :: h2so4_m3 ! Number concentration of H2SO4 (m-3)
68
69  ! RADII GRID (m)
70  real, save, dimension(:), allocatable :: rad_cld,ri,rs,vol
71  real, save ::  vratio
72
73
74
75
76  ! FIADERO'S CORRECTION
77
78  !! This flag enables/disables the __Fiadero__ correction alogrithm for fractal mode settling velocity
79  !! computation.
80  !!
81  !! @bug
82  !! Currently, the Fiadero correction creates instatibilities on the vertical structure. It seems to be
83  !! related to the coupling between the two moments. In order to reduce the instabilities, settling
84  !! velocity of moments are forced to be the same, see [[mm_globals(module):mm_wsed_m0(variable)]] and
85  !! [[mm_globals(module):mm_wsed_m3(variable)]]).
86  LOGICAL, SAVE          :: no_fiadero_w = .false.
87  !> Minimum ratio for __Fiadero__ correction.
88  !!
89  !! When [[mm_globals(module):mm_no_fiadero_w(variable)]] is disabled, this variable defines the minimum
90  !! value of the moment's ratio between two adjacents vertical cells to be used within the correction.
91  REAL, SAVE :: fiadero_min  = 0.1D0
92  !> Maximum ratio for __Fiadero__ correction.
93  !!
94  !! When [[mm_globals(module):mm_no_fiadero_w(variable)]] is disabled, this variable defines the maximum
95  !! value of the moment's ratio between two adjacents vertical cells to be used within the correction.
96  REAL, SAVE :: fiadero_max  = 10.D0
97
98  LOGICAL, SAVE :: wsed_m0 = .false. !! Force all aerosols moments to fall at M0 settling velocity.
99  LOGICAL, SAVE :: wsed_m3 = .false. !! Force all aerosols moments to fall at M3 settling velocity.
100
101
102
103contains
104  !  subroutine   build_radius_grid
105  !  SUBROUTINE   logdist   Calculates the lognormal size distribution function with bins
106
107
108!******************************************************************************
109  SUBROUTINE build_radius_grid(nbins,rmi,rma,vratio)
110!******************************************************************************
111    INTEGER, INTENT(in)                                :: nbins
112    REAL, INTENT(in)                     :: rmi,rma
113    REAL, INTENT(out)                    :: vratio
114    INTEGER :: i
115
116    if (allocated(rad_cld)) deallocate(rad_cld)
117    if (allocated(ri)) deallocate(ri)
118    if (allocated(rs)) deallocate(rs)
119    if (allocated(vol)) deallocate(vol)
120    ALLOCATE(rad_cld(nbins),ri(nbins),rs(nbins),vol(nbins))
121 
122    vratio=(rma/rmi)**(3.D0/(nbins-1))
123    vol(1)=4.D0/3.D0*pi*rmi**3
124
125    DO i=1,nbins
126      rad_cld(i)=rmi*vratio**(i/3.D0)
127      IF (i < nbins) vol(i+1)=vol(1)*vratio**i
128      ri(i) = (2.D0/(vratio+1.))**(1.D0/3.D0)*rad_cld(i)
129      rs(i) = (2.D0*vratio/(vratio+1.D0))**(1.D0/3.D0)*rad_cld(i)
130    ENDDO
131
132  END SUBROUTINE build_radius_grid
133
134
135!******************************************************************************
136  SUBROUTINE logdist(sigma,ntotal,r0,rad,n_aer)
137!******************************************************************************
138
139    USE free_param
140    implicit none
141   
142    ! Inputs / Outputs
143    real,intent(in) :: sigma, ntotal, r0
144    real,intent(out) :: n_aer(nbin)
145    real,intent(in) :: rad(nbin)
146
147    ! Local variables
148    real :: lognr,dr,n_aer_erf(nbin),sqr2sig,logsig
149    integer :: i
150
151    dr = ((2.D0*vratio)/(vratio +1.D0))**(1.D0/3.D0) - (2.D0/(vratio + 1.D0))**(1.D0/3.D0)
152
153    logsig = log(sigma)
154    sqr2sig = logsig*sqrt(2.0)
155
156    OPEN(666,FILE="logn.dat")
157
158    DO i=1,nbin
159       lognr = 1.D0 / (sqrt(2.D0*PI)*logsig*rad(i))               !m-1
160       lognr = lognr * exp(-0.5D0*(log(rad(i)/r_aer)/logsig)**2)  !m-1
161       n_aer(i) = lognr*dr*rad(i) !#
162       n_aer_erf(i) =  0.5 * (erf(log(rs(i)/r_aer)/sqr2sig) - erf(log(ri(i)/r_aer)/sqr2sig))
163       WRITE(666,'(6(ES15.7,2X))') rad(i),lognr,n_aer(i), n_aer_erf(i), rad(i)*dr, rs(i)-ri(i)
164    END DO
165
166    CLOSE(666)
167
168!    write(*,'(a,2(ES15.7,1X))') "logdist: nAER(norm), ERF method = ", SUM(n_aer(:)),SUM(n_aer_erf)
169    n_aer(:) = n_aer(:)*ntotal
170!    write(*,'((a),2(ES15.7,1X))') '  -->      total', SUM(n_aer(:)), ntotal
171!    write(*,'((a),ES15.7)')       '  --> rel. error', abs(SUM(n_aer(:))-ntotal)/ntotal
172!    write(*,'(a)') 'Using erf METHOD (more accurate)'
173    n_aer(:) = n_aer_erf(:) * ntotal
174
175  END SUBROUTINE logdist
176
177END MODULE donnees
Note: See TracBrowser for help on using the repository browser.