source: LMDZ6/trunk/libf/phylmd/cosp/dsd.F90 @ 4103

Last change on this file since 4103 was 4103, checked in by Laurent Fairhead, 2 years ago

Inclusion of some corrections and optimisations for XIOS done by
Arnaud Durocher during his TGCC mission.
Included here are r3703, r3704, r3750, r3751, r3752 from his
LMDZ6/branches/Optimisation_LMDZ branch

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 10.4 KB
Line 
1  subroutine dsd(Q,Re,Np,D,N,nsizes,dtype,rho_a,tk, &
2             dmin,dmax,apm,bpm,rho_c,p1,p2,p3)
3  use array_lib
4  use math_lib
5  implicit none
6
7! Purpose:
8!   Create a discrete drop size distribution
9!
10!   Starting with Quickbeam V3, this routine now allows input of
11!   both effective radius (Re) and total number concentration (Nt)
12!   Roj Marchand July 2010
13!
14!   The version in Quickbeam v.104 was modified to allow Re but not Nt
15!   This is a significantly modified form for the version     
16!
17!   Originally Part of QuickBeam v1.03 by John Haynes
18!   http://reef.atmos.colostate.edu/haynes/radarsim
19!
20! Inputs:
21!
22!   [Q]        hydrometeor mixing ratio (g/kg)
23!   [Re]       Optional Effective Radius (microns).  0 = use defaults (p1, p2, p3)
24!
25!   [D]        array of discrete drop sizes (um) where we desire to know the number concentraiton n(D).
26!   [nsizes]   number of elements of [D]
27!
28!   [dtype]    distribution type
29!   [rho_a]    ambient air density (kg m^-3)
30!   [tk]       temperature (K)
31!   [dmin]     minimum size cutoff (um)
32!   [dmax]     maximum size cutoff (um)
33!   [rho_c]    alternate constant density (kg m^-3)
34!   [p1],[p2],[p3]  distribution parameters
35!
36! Input/Output:
37!   [apm]      a parameter for mass (kg m^[-bpm])
38!   [bmp]      b params for mass
39!
40! Outputs:
41!   [N]        discrete concentrations (cm^-3 um^-1)
42!              or, for monodisperse, a constant (1/cm^3)
43!
44! Requires:
45!   function infind
46!
47! Created:
48!   11/28/05  John Haynes (haynes@atmos.colostate.edu)
49! Modified:
50!   01/31/06  Port from IDL to Fortran 90
51!   07/07/06  Rewritten for variable DSD's
52!   10/02/06  Rewritten using scaling factors (Roger Marchand and JMH), Re added V1.04
53!   July 2020 "N Scale factors" (variable fc) removed (Roj Marchand).
54 
55! ----- INPUTS ----- 
56 
57  integer, intent(in) :: nsizes
58  integer, intent(in) :: dtype
59  real*8, intent(in)  :: Q,Re_,Np,D(nsizes)
60  real*8, intent(in)  :: rho_a,tk,dmin,dmax,rho_c,p1,p2,p3
61   
62  real*8, intent(inout) :: apm,bpm 
63 
64! ----- OUTPUTS -----
65
66  real*8, intent(out) :: N(nsizes)
67 
68! ----- INTERNAL -----
69 
70   real*8 :: fc(nsizes)
71
72  real*8 :: &
73  N0,D0,vu,local_np,dm,ld, &            ! gamma, exponential variables
74  dmin_mm,dmax_mm,ahp,bhp, &        ! power law variables
75  rg,log_sigma_g, &         ! lognormal variables
76  rho_e                 ! particle density (kg m^-3)
77 
78  real*8 :: tmp1, tmp2
79  real*8 :: pi,rc,tc
80  real*8 :: Re
81
82  integer k,lidx,uidx
83
84  Re = Re_
85
86  tc = tk - 273.15
87  pi = acos(-1.0)
88 
89  ! // if density is constant, store equivalent values for apm and bpm
90  if ((rho_c > 0) .and. (apm < 0)) then
91    apm = (pi/6)*rho_c
92    bpm = 3.
93  endif
94 
95  ! will preferentially use Re input over Np.
96  ! if only Np given then calculate Re
97  ! if neigher than use other defaults (p1,p2,p3) following quickbeam documentation
98  if(Re==0 .and. Np>0) then
99   
100        call calc_Re(Q,Np,rho_a, &
101             dtype,dmin,dmax,apm,bpm,rho_c,p1,p2,p3, &
102             Re)
103  endif
104 
105 
106  select case(dtype)
107 
108! ---------------------------------------------------------!
109! // modified gamma                                        !
110! ---------------------------------------------------------!
111! :: np = total number concentration
112! :: D0 = characteristic diameter (um)
113! :: dm = mean diameter (um) - first moment over zeroth moment
114! :: vu = distribution width parameter
115
116  case(1) 
117 
118    if( abs(p3+2) < 1E-8) then
119 
120    if( Np>1E-30) then
121   
122        ! Morrison scheme with Martin 1994 shape parameter (NOTE: vu = pc +1)
123        ! fixed Roj. Dec. 2010 -- after comment by S. Mcfarlane
124        vu = (1/(0.2714 + 0.00057145*Np*rho_a*1E-6))**2.0 ! units of Nt = Np*rhoa = #/cm^3
125    else
126        print *, 'Error: Must specify a value for Np in each volume', &
127             ' with Morrison/Martin Scheme.'
128            stop   
129    endif
130   
131    elseif (abs(p3+1) > 1E-8) then
132
133      ! vu is fixed in hp structure 
134      vu = p3
135
136    else
137
138      ! vu isn't specified
139     
140      print *, 'Error: Must specify a value for vu for Modified Gamma distribution'
141      stop   
142     
143    endif
144     
145      if(Re>0) then
146
147    D0 = 2.0*Re*gamma(vu+2)/gamma(vu+3)
148   
149        fc = ( &
150             ((D*1E-6)**(vu-1)*exp(-1*D/D0)) / &
151             (apm*((D0*1E-6)**(vu+bpm))*gamma(vu+bpm)) &
152         ) * 1E-12
153
154        N = fc*rho_a*(Q*1E-3)
155       
156      elseif( p2+1 > 1E-8) then     ! use default value for MEAN diameter
157     
158        dm = p2
159    D0 = gamma(vu)/gamma(vu+1)*dm
160
161        fc = ( &
162             ((D*1E-6)**(vu-1)*exp(-1*D/D0)) / &
163             (apm*((D0*1E-6)**(vu+bpm))*gamma(vu+bpm)) &
164         ) * 1E-12
165
166        N = fc*rho_a*(Q*1E-3)
167       
168      elseif(abs(p3+1) > 1E-8)  then! use default number concentration
169   
170        local_np = p1 ! total number concentration / pa check
171   
172    tmp1 = (Q*1E-3)**(1./bpm)
173     
174        fc = (D*1E-6 / (gamma(vu)/(apm*local_np*gamma(vu+bpm)))** &
175             (1./bpm))**vu
176         
177        N = ( &
178          (rho_a*local_np*fc*(D*1E-6)**(-1.))/(gamma(vu)*tmp1**vu) * &
179          exp(-1.*fc**(1./vu)/tmp1) &
180      ) * 1E-12
181
182      else
183     
184        print *, 'Error:  No default value for Dm or Np provided!  '
185        stop
186       
187      endif
188   
189   
190! ---------------------------------------------------------!
191! // exponential                                           !
192! ---------------------------------------------------------!
193! :: N0 = intercept parameter (m^-4)
194! :: ld = slope parameter (um)
195
196  case(2)
197 
198    if(Re>0) then
199 
200        ld = 1.5/Re   ! units 1/um
201       
202    fc = (ld*1E6)**(1.+bpm)/(apm*gamma(1+bpm))* &
203               exp(-1.*(ld*1E6)*(D*1E-6))*1E-12
204     
205        N = fc*rho_a*(Q*1E-3)
206       
207    elseif (abs(p1+1) > 1E-8) then
208
209    ! use N0 default value
210   
211        N0 = p1
212
213        tmp1 = 1./(1.+bpm)
214 
215        fc = ((apm*gamma(1.+bpm)*N0)**tmp1)*(D*1E-6)
216 
217        N = ( &
218            N0*exp(-1.*fc*(1./(rho_a*Q*1E-3))**tmp1) &
219    ) * 1E-12
220
221    elseif (abs(p2+1) > 1E-8) then
222
223    !     used default value for lambda
224        ld = p2
225
226        fc = (ld*1E6)**(1.+bpm)/(apm*gamma(1+bpm))* &
227             exp(-1.*(ld*1E6)*(D*1E-6))*1E-12
228     
229        N = fc*rho_a*(Q*1E-3)
230
231    else
232
233      !  ld "parameterized" from temperature (carry over from original Quickbeam).
234      ld = 1220*10.**(-0.0245*tc)*1E-6
235      N0 = ((ld*1E6)**(1+bpm)*Q*1E-3*rho_a)/(apm*gamma(1+bpm))
236   
237      N = ( &
238          N0*exp(-1*ld*D) &
239          ) * 1E-12
240   
241    endif
242 
243! ---------------------------------------------------------!
244! // power law                                             !
245! ---------------------------------------------------------!
246! :: ahp = Ar parameter (m^-4 mm^-bhp)
247! :: bhp = br parameter
248! :: dmin_mm = lower bound (mm)
249! :: dmax_mm = upper bound (mm)
250
251  case(3)
252 
253    if(Re>0) then
254        print *, 'Variable Re not supported for ', &
255         'Power-Law distribution'
256    stop
257    elseif(Np>0) then
258        print *, 'Variable Np not supported for ', &
259         'Power-Law distribution'
260    stop
261    endif
262
263!   :: br parameter
264    if (abs(p1+2) < 1E-8) then
265!     :: if p1=-2, bhp is parameterized according to Ryan (2000),
266!     :: applicatable to cirrus clouds
267      if (tc < -30) then
268        bhp = -1.75+0.09*((tc+273)-243.16)
269      elseif ((tc >= -30) .and. (tc < -9)) then
270        bhp = -3.25-0.06*((tc+273)-265.66)
271      else
272        bhp = -2.15
273      endif
274    elseif (abs(p1+3) < 1E-8) then     
275!     :: if p1=-3, bhp is parameterized according to Ryan (2000),
276!     :: applicable to frontal clouds
277      if (tc < -35) then
278        bhp = -1.75+0.09*((tc+273)-243.16)
279      elseif ((tc >= -35) .and. (tc < -17.5)) then
280        bhp = -2.65+0.09*((tc+273)-255.66)
281      elseif ((tc >= -17.5) .and. (tc < -9)) then
282        bhp = -3.25-0.06*((tc+273)-265.66)
283      else
284        bhp = -2.15
285      endif   
286    else
287!     :: otherwise the specified value is used
288      bhp = p1
289    endif
290
291!   :: Ar parameter
292    dmin_mm = dmin*1E-3
293    dmax_mm = dmax*1E-3
294
295!   :: commented lines are original method with constant density
296      ! rc = 500.       ! (kg/m^3)
297      ! tmp1 = 6*rho_a*(bhp+4)
298      ! tmp2 = pi*rc*(dmax_mm**(bhp+4))*(1-(dmin_mm/dmax_mm)**(bhp+4))
299      ! ahp = (Q*1E-3)*1E12*tmp1/tmp2
300
301!   :: new method is more consistent with the rest of the distributions
302!   :: and allows density to vary with particle size
303      tmp1 = rho_a*(Q*1E-3)*(bhp+bpm+1)
304      tmp2 = apm*(dmax_mm**bhp*dmax**(bpm+1)-dmin_mm**bhp*dmin**(bpm+1))
305      ahp = tmp1/tmp2 * 1E24
306      ! ahp = tmp1/tmp2
307 
308      lidx = infind(D,dmin)
309      uidx = infind(D,dmax)   
310      do k=lidx,uidx
311 
312        N(k) = ( &
313        ahp*(D(k)*1E-3)**bhp &
314    ) * 1E-12   
315
316      enddo
317
318    ! print *,'test=',ahp,bhp,ahp/(rho_a*Q),D(100),N(100),bpm,dmin_mm,dmax_mm
319
320! ---------------------------------------------------------!
321! // monodisperse                                          !
322! ---------------------------------------------------------!
323! :: D0 = particle diameter (um)
324
325  case(4)
326 
327    if (Re>0) then
328        D0 = Re
329    else
330        D0 = p1
331    endif
332   
333      rho_e = (6/pi)*apm*(D0*1E-6)**(bpm-3)
334      fc(1) = (6./(pi*D0**3*rho_e))*1E12
335      N(1) = fc(1)*rho_a*(Q*1E-3)
336   
337! ---------------------------------------------------------!
338! // lognormal                                             !
339! ---------------------------------------------------------!
340! :: N0 = total number concentration (m^-3)
341! :: np = fixed number concentration (kg^-1)
342! :: rg = mean radius (um)
343! :: log_sigma_g = ln(geometric standard deviation)
344
345  case(5)
346    if (abs(p1+1) < 1E-8 .or. Re>0 ) then
347
348!     // rg, log_sigma_g are given
349      log_sigma_g = p3
350      tmp2 = (bpm*log_sigma_g)**2.
351      if(Re.le.0) then
352        rg = p2
353      else
354    rg =Re*exp(-2.5*(log_sigma_g**2))
355      endif
356 
357         fc = 0.5 * ( &
358         (1./((2.*rg*1E-6)**(bpm)*apm*(2.*pi)**(0.5) * &
359         log_sigma_g*D*0.5*1E-6)) * &
360         exp(-0.5*((log(0.5*D/rg)/log_sigma_g)**2.+tmp2)) &
361         ) * 1E-12
362               
363      N = fc*rho_a*(Q*1E-3)
364     
365    elseif (abs(p2+1) < 1E-8 .or. Np>0) then
366
367!     // Np, log_sigma_g are given   
368      if(Np>0) then
369        local_Np=Np
370      else
371        local_Np = p1
372      endif
373     
374      log_sigma_g = p3
375      N0 = local_np*rho_a
376      tmp1 = (rho_a*(Q*1E-3))/(2.**bpm*apm*N0)
377      tmp2 = exp(0.5*bpm**2.*(log_sigma_g))**2.     
378      rg = ((tmp1/tmp2)**(1/bpm))*1E6
379     
380      N = 0.5*( &
381        N0 / ((2.*pi)**(0.5)*log_sigma_g*D*0.5*1E-6) * &
382    exp((-0.5*(log(0.5*D/rg)/log_sigma_g)**2.)) &
383    ) * 1E-12     
384     
385    else
386
387      print *, 'Error: Must specify a value for sigma_g'
388      stop
389   
390    endif
391   
392  end select
393 
394  end subroutine dsd
Note: See TracBrowser for help on using the repository browser.