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

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

SL: Cloud model for Venus. Not validated yet.

File size: 5.3 KB
Line 
1
2!  SUBROUTINE   MERGING   Mode merging calculations
3!  FUNCTION     U         For the donor mode
4!  FUNCTION     ALPHA
5!  FUNCTION     BETA
6!  SUBROUTINE   GetN1R1
7!  SUBROUTINE   GetN2R2
8
9
10!*****************************************************************************
11SUBROUTINE MERGING(rini,ni,sigmai,sigmaf,dM0i,dM3i,dM0f,dM3f)
12
13  ! Example: mode 1 merge to mode 2
14  ! dMi and dMf are the fraction of moment need to be
15  ! additioned to M_2 and replace for M_1
16
17  use donnees
18  IMPLICIT NONE
19
20  ! Inputs
21  real, intent(in) :: rini, ni, sigmai, sigmaf
22  ! Outputs
23  real, intent(out) :: dM0i,dM3i,dM0f,dM3f
24  ! Local varialbes
25  real :: Nt1,Rt1,Nt2,Rt2
26  ! Functions
27  real :: moment
28
29  ! A mode is free to move anywhere in size space, it has a preferred position,
30  ! called home base rhb1 for mode 1 and rhb2 for mode 2
31
32  ! Calculation of the new N1,R1,N2 and R2 after mode-merging
33  CALL GetN1R1(ni,rini,Nt1,Rt1,sigmai)
34  CALL GetN2R2(ni,rini,Nt2,Rt2,sigmai,sigmaf)
35
36  ! BE CAREFUL: here the moment are not normalized
37  dM0i = moment(0,Nt1,Rt1,sigmai)
38  dM3i = moment(3,Nt1,Rt1,sigmai)
39
40  dM0f = moment(0,Nt2,Rt2,sigmaf)
41  dM3f = moment(3,Nt2,Rt2,sigmaf)
42
43  RETURN
44END SUBROUTINE MERGING
45
46
47!*****************************************************************************
48FUNCTION U(rini,k,sigmai)
49
50  !*     Computes [ln(Redge)-ln(Ri) - k*ln(sigmai)**2]/ [SQRT(2)*ln(sigmai)]
51  !*     for the donor mode
52  !*
53  !*     INPUTS
54  !*           rini     mean radius of donor mode before mode-merging
55  !*           k        moment order used for computation
56  !*
57  !*     OUTPUTS
58  !*           U        a function of the log-N distrib parameters
59  !*
60  !*     See also: J.B. notes about mode-merging
61
62  use donnees
63  IMPLICIT NONE
64
65  real, intent(in) :: rini, k, sigmai
66  real :: U
67
68  U = (log(redge)-log(rini)-k*log(sigmai)**2)/(sqrt(2.)*log(sigmai))
69
70  RETURN
71END FUNCTION U
72
73
74!*****************************************************************************
75FUNCTION ALPHA(rini,k,sigmai)
76
77  !*     Computes: 1 + erf(u(param,k)) for the donor mode
78  !*
79  !*     INPUTS
80  !*           rini     Mean radius of donor mode before mode-merging
81  !*           k        Moment order used for computation
82  !*
83  !*     OUTPUTS
84  !*           ALPHA    error of the donor mode
85  !*
86  !*     See also: J.B. notes about mode-merging
87
88  IMPLICIT NONE
89
90  ! Imputs
91  real, intent(in) :: rini, k, sigmai
92  ! Function
93  REAL ::  U, ALPHA
94
95  ALPHA = 1.0D0 + erf(U(rini,k,sigmai))
96
97  RETURN
98END FUNCTION ALPHA
99
100
101!*****************************************************************************
102FUNCTION BETA(rini,k,sigmai)
103
104  !*     Computes: 1 - erf(u(param,k)) for the donor mode
105  !*
106  !*     INPUTS
107  !*           rini     Mean radius of donor mode before mode-merging
108  !*           k        Moment order used for computation
109  !*
110  !*     OUTPUTS
111  !*           BETA     Error of the donor mode
112  !*     
113  !*     See also: J.B. notes about mode-merging
114
115  IMPLICIT NONE
116
117  ! Imputs
118  real, intent(in) :: rini, k, sigmai
119  ! Function
120  REAL :: U, BETA
121
122  BETA = 1.D0 - erf(U(rini,k,sigmai))
123
124  RETURN
125END FUNCTION BETA
126
127
128!*****************************************************************************
129SUBROUTINE GetN1R1(ni,rini,Nt1,Rt1,sigmai)
130
131  !*     Computes the final Mean radius and total number particles for donor mode
132  !*
133  !*     INPUTS
134  !*           rini     Mean radius of donor mode before mode-merging
135  !*           ni       Total number of particles at initial state
136  !*
137  !*     OUTPUTS
138  !*     A tuple (N1,R1) with the total number of particles and Mean radius of mode 1
139  !*           N1       Total number of particles of donor mode after mode-merging
140  !*           R1       Mean radius of donor mode after mode-merging
141  !*
142  !*    See also : J.B. notes about mode-merging
143
144  IMPLICIT NONE
145
146  ! Imputs
147  real, intent(in) :: ni,rini,sigmai
148  ! Outputs
149  real, intent(out) :: Nt1,Rt1
150  ! Function
151  REAL :: ALPHA
152  ! Local variables
153  REAL :: cn1, cr1, p, q, a, b
154
155  p = 3.0D0
156  q = 6.0D0
157
158  a = ALPHA(rini,p,sigmai)
159  b = ALPHA(rini,q,sigmai)
160
161  cn1 = ni/2.0D0
162  cr1 = rini
163
164  Nt1 = cn1 * a / (a/b)**(p/(p-q))
165  Rt1 = cr1 * (a / b)**(1.D0/(p-q))
166
167  RETURN
168END SUBROUTINE GetN1R1
169
170
171!*****************************************************************************
172SUBROUTINE GetN2R2(ni,rini,N2,R2,sigmai,sigmaf)
173
174  !*     Computes the final Mean radius and total number of particles for
175  !*     the receptor mode
176  !*
177  !*     FUNCTION
178  !*           BETA
179  !*     
180  !*     INPUTS
181  !*           rini     Mean radius of donor mode before mode-merging
182  !*           ni       Total number of particles at initial state
183  !*
184  !*     OUTPUTS
185  !*     A tuple (N2,R2) with the total number of particles and Mean radius of mode 2
186  !*           N2       Total number of particles of receptor mode after mode-merging
187  !*           R2       Mean radius of receptor mode after mode-merging
188  !*
189  !*     See also : J.B. notes about mode-merging
190
191  IMPLICIT NONE
192
193  ! Imputs
194  REAL :: sigmai, sigmaf
195  real :: ni, rini, N2, R2
196  ! Local variables
197  real :: a, b, cn2, cr2, p, q
198  ! Function
199  REAL :: BETA
200
201  p = 3.0D0
202  q = 6.0D0
203
204  a = BETA(rini,p,sigmai)
205  b = BETA(rini,q,sigmai)
206
207  cn2 = ni/2.D0 *exp(-0.5D0*p*q * (log(sigmai)**2 - log(sigmaf)**2))
208  cr2 = rini * exp(0.5D0* (p+q) * (log(sigmai)**2 - log(sigmaf)**2))
209
210  N2 = cn2 * a/(a/b)**(p/(p-q))
211  R2 = cr2 * (a/b)**(1.D0/(p-q))
212
213  RETURN
214END SUBROUTINE GetN2R2
Note: See TracBrowser for help on using the repository browser.