source: LMDZ6/branches/Amaury_dev/libf/phylmd/cosp/calc_Re.F90

Last change on this file was 5185, checked in by abarral, 2 months ago

Replace REPROBUS CPP KEY by logical using handmade wonky wrapper

File size: 7.1 KB
RevLine 
[2432]1  subroutine calc_Re(Q,Np,rho_a, &
2             dtype,dmin,dmax,apm,bpm,rho_c,p1,p2,p3, &
3             Re)
4  use math_lib
5  implicit none
6
7! Purpose:
8!   Calculates Effective Radius (1/2 distribution 3rd moment / 2nd moment).
[5099]9
[2432]10!   For some distribution types, the total number concentration (per kg), Np
11!   may be optionally specified.   Should be set to zero, otherwise.
[5099]12
[2432]13!   Roj Marchand July 2010
14
15
16! Inputs:
[5099]17
[2432]18!   [Q]        hydrometeor mixing ratio (g/kg)  ! not needed for some distribution types
19!   [Np]       Optional Total number concentration (per kg).  0 = use defaults (p1, p2, p3)
[5099]20
[2432]21!   [rho_a]    ambient air density (kg m^-3)   
[5099]22
[2432]23!   Distribution parameters as per quickbeam documentation.
24!   [dtype]    distribution type
25!   [dmin]     minimum size cutoff (um)
26!   [dmax]     maximum size cutoff (um)
27!   [apm]      a parameter for mass (kg m^[-bpm])
28!   [bmp]      b params for mass
29!   [p1],[p2],[p3]  distribution parameters
[5099]30
31
[2432]32! Outputs:
33!   [Re]       Effective radius, 1/2 the 3rd moment/2nd moment (um)
[5099]34
[2432]35! Created:
36!   July 2010  Roj Marchand
37
38! ----- INPUTS ----- 
39 
[5095]40  real*8, intent(in) :: Q,Np,rho_a
[2432]41 
42  integer, intent(in):: dtype
[5095]43  real*8, intent(in) :: dmin,dmax,rho_c,p1,p2,p3
[2432]44   
[5095]45  real*8, intent(inout) :: apm,bpm 
[2432]46   
47! ----- OUTPUTS -----
48
[5095]49  real*8, intent(out) :: Re
[2432]50 
51! ----- INTERNAL -----
52 
53  integer :: local_dtype
[5095]54  real*8  :: local_p3,local_Np
[2432]55
[5095]56  real*8 :: pi, &
[2432]57  N0,D0,vu,dm,ld, &         ! gamma, exponential variables
58  rg,log_sigma_g
59 
[5095]60  real*8 :: tmp1,tmp2
[2432]61
62  pi = acos(-1.0)
63
64  ! // if density is constant, set equivalent values for apm and bpm
[5185]65  if ((rho_c > 0) .AND. (apm < 0)) then
[2432]66    apm = (pi/6)*rho_c
67    bpm = 3.
68  endif
69
70  ! Exponential is same as modified gamma with vu =1
71  ! if Np is specified then we will just treat as modified gamma
[5185]72  if(dtype.eq.2 .AND. Np>0) then
[2432]73    local_dtype=1;
74    local_p3=1;
75  else
76    local_dtype=dtype;
77    local_p3=p3;
78  endif
79 
80  select case(local_dtype)
81 
82! ---------------------------------------------------------!
83! // modified gamma                                        !
84! ---------------------------------------------------------!
85! :: Np = total number concentration (1/kg) = Nt / rho_a
86! :: D0 = characteristic diameter (um)
87! :: dm = mean diameter (um) - first moment over zeroth moment
88! :: vu = distribution width parameter
89
90  case(1) 
91 
92    if( abs(local_p3+2) < 1E-8) then
93 
94    if(Np>1E-30) then
95        ! Morrison scheme with Martin 1994 shape parameter (NOTE: vu = pc +1)
96        ! fixed Roj. Dec. 2010 -- after comment by S. Mcfarlane
97        vu = (1/(0.2714 + 0.00057145*Np*rho_a*1E-6))**2 ! units of Nt = Np*rhoa = #/cm^3
98    else
[5160]99        PRINT *, 'Error: Must specify a value for Np in each volume', &
[2432]100             ' with Morrison/Martin Scheme.'
101            stop   
102    endif
103   
104    elseif (abs(local_p3+1) > 1E-8) then
105
106      ! vu is fixed in hp structure 
107      vu = local_p3
108
109    else
110
111      ! vu isn't specified
112     
[5160]113      PRINT *, 'Error: Must specify a value for vu for Modified Gamma distribution'
[2432]114      stop   
115     
116    endif
117   
118
[5185]119    if( Np.eq.0 .AND. p2+1 > 1E-8) then     ! use default value for MEAN diameter as first default
[2432]120     
121        dm = p2             ! by definition, should have units of microns
122    D0 = gamma(vu)/gamma(vu+1)*dm
123       
124    else   ! use value of Np
125       
[5095]126        if(Np.eq.0) then
[2432]127       
128            if( abs(p1+1) > 1E-8 ) then  !   use default number concentration
129           
130                local_Np = p1 ! total number concentration / pa --- units kg^-1
131            else
[5160]132            PRINT *, 'Error: Must specify Np or default value ', &
[2432]133                 '(p1=Dm [um] or p2=Np [1/kg]) for ', &
134                 'Modified Gamma distribution'
135                stop
136            endif
137        else
138            local_Np=Np;   
139    endif
140   
141    D0 = 1E6 * ( Q*1E-3*gamma(vu)/(apm*local_Np*gamma(vu+bpm)) )**(1/bpm)  ! units = microns
142
143    endif 
144     
145    Re = 0.5*D0*gamma(vu+3)/gamma(vu+2)
146   
147   
148! ---------------------------------------------------------!
149! // exponential                                           !
150! ---------------------------------------------------------!
151! :: N0 = intercept parameter (m^-4)
152! :: ld = slope parameter (um)
153
154  case(2)
155 
156    ! Np not specified (see if statement above)
157 
158    if((abs(p1+1) > 1E-8) ) then   ! N0 has been specified, determine ld
159   
160        N0 = p1
161    tmp1 = 1./(1.+bpm)
162    ld = ((apm*gamma(1.+bpm)*N0)/(rho_a*Q*1E-3))**tmp1
163    ld = ld/1E6                     ! set units to microns^-1
164       
165    elseif (abs(p2+1) > 1E-8) then  ! lambda=ld has been specified as default
166
167        ld = p2     ! should have units of microns^-1
168   
169    else
170   
[5160]171    PRINT *, 'Error: Must specify Np or default value ', &
[2432]172         '(p1=No or p2=lambda) for Exponential distribution'
173        stop
174       
175    endif
176
177    Re = 1.5/ld ;
178 
179! ---------------------------------------------------------!
180! // power law                                             !
181! ---------------------------------------------------------!
182! :: ahp = Ar parameter (m^-4 mm^-bhp)
183! :: bhp = br parameter
184! :: dmin_mm = lower bound (mm)
185! :: dmax_mm = upper bound (mm)
186
187  case(3)
188
189    Re=0;  ! Not supporting LUT approach for power-law ...
190
191    if(Np>0) then
192   
[5160]193        PRINT *, 'Variable Np not supported for ', &
[2432]194         'Power Law distribution'
195        stop
196    endif
197! ---------------------------------------------------------!
198! // monodisperse                                          !
199! ---------------------------------------------------------!
200! :: D0 = particle diameter (um) == Re
201
202  case(4)
203 
204        Re = p1
205   
206        if(Np>0) then
[5160]207        PRINT *, 'Variable Np not supported for ', &
[2432]208         'Monodispersed distribution'
209        stop
210    endif
211   
212! ---------------------------------------------------------!
213! // lognormal                                             !
214! ---------------------------------------------------------!
215! :: N0 = total number concentration (m^-3)
216! :: np = fixed number concentration (kg^-1)
217! :: rg = mean radius (um)
218! :: log_sigma_g = ln(geometric standard deviation)
219
220  case(5)
221 
222        if( abs(local_p3+1) > 1E-8 ) then
223
224            !set natural log width
225            log_sigma_g = local_p3
226        else
[5160]227            PRINT *, 'Error: Must specify a value for sigma_g ', &
[2432]228             'when using a Log-Normal distribution'
229            stop
230        endif
231     
232    ! get rg ...
[5185]233    if( Np.eq.0 .AND. (abs(p2+1) > 1E-8) ) then ! use default value of rg
[2432]234   
235            rg = p2
236             
237        else
238            if(Np>0) then
239           
240                local_Np=Np;
241               
242            elseif(abs(p2+1) < 1E-8) then
243           
244                local_Np=p1
245            else
[5160]246                PRINT *, 'Error: Must specify Np or default value ', &
[2432]247                 '(p2=Rg or p1=Np) for Log-Normal distribution'
248            endif
249           
250            log_sigma_g = p3
251            tmp1 = (Q*1E-3)/(2.**bpm*apm*local_Np)
252            tmp2 = exp(0.5*bpm**2.*(log_sigma_g))**2.     
253            rg = ((tmp1/tmp2)**(1/bpm))*1E6
254        endif
255               
256        Re = rg*exp(+2.5*(log_sigma_g**2))
257       
258  end select
259 
260  end subroutine calc_Re
Note: See TracBrowser for help on using the repository browser.