source: trunk/LMDZ.GENERIC/libf/phystd/radii_mod.F90 @ 1309

Last change on this file since 1309 was 1308, checked in by emillour, 10 years ago

Generic GCM:
Some cleanup to simplify dynamics/physics interactions by getting rid
of dimphys.h (i.e. the nlayermx parameter) and minimizing use of
dimension.h in the physics.
EM

File size: 12.1 KB
Line 
1!==================================================================
2module radii_mod
3!==================================================================
4!  module to centralize the radii calculations for aerosols
5! OK for water but should be extended to other aerosols (CO2,...)
6!==================================================================
7     
8!     water cloud optical properties
9     
10      real, save ::  rad_h2o
11      real, save ::  rad_h2o_ice
12      real, save ::  Nmix_h2o
13      real, save ::  Nmix_h2o_ice
14      real, parameter ::  coef_chaud=0.13
15      real, parameter ::  coef_froid=0.09
16
17
18      contains
19
20
21!==================================================================
22   subroutine su_aer_radii(ngrid,nlayer,reffrad,nueffrad)
23!==================================================================
24!     Purpose
25!     -------
26!     Compute the effective radii of liquid and icy water particles
27!
28!     Authors
29!     -------
30!     Jeremy Leconte (2012)
31!
32!==================================================================
33 ! to use  'getin'
34      use ioipsl_getincom
35      use radinc_h, only: naerkind
36      use aerosol_mod
37!      USE tracer_h
38      Implicit none
39
40      include "callkeys.h"
41!      include "dimensions.h"
42!      include "dimphys.h"
43
44      integer,intent(in) :: ngrid
45      integer,intent(in) :: nlayer
46
47      real, intent(out) :: reffrad(ngrid,nlayer,naerkind)      !aerosols radii (K)
48      real, intent(out) :: nueffrad(ngrid,nlayer,naerkind)     !variance     
49
50      logical, save :: firstcall=.true.
51      integer :: iaer   
52     
53      print*,'enter su_aer_radii'
54          do iaer=1,naerkind
55!     these values will change once the microphysics gets to work
56!     UNLESS tracer=.false., in which case we should be working with
57!     a fixed aerosol layer, and be able to define reffrad in a
58!     .def file. To be improved!
59
60            if(iaer.eq.iaero_co2)then ! CO2 ice
61               reffrad(1:ngrid,1:nlayer,iaer) = 1.e-4
62               nueffrad(1:ngrid,1:nlayer,iaer) = 0.1
63            endif
64
65            if(iaer.eq.iaero_h2o)then ! H2O ice
66               reffrad(1:ngrid,1:nlayer,iaer) = 1.e-5
67               nueffrad(1:ngrid,1:nlayer,iaer) = 0.1
68            endif
69
70            if(iaer.eq.iaero_dust)then ! dust
71               reffrad(1:ngrid,1:nlayer,iaer) = 1.e-5
72               nueffrad(1:ngrid,1:nlayer,iaer) = 0.1
73            endif
74 
75            if(iaer.eq.iaero_h2so4)then ! H2O ice
76               reffrad(1:ngrid,1:nlayer,iaer) = 1.e-6
77               nueffrad(1:ngrid,1:nlayer,iaer) = 0.1
78            endif
79           
80            if(iaer.eq.iaero_back2lay)then ! Two-layer aerosols
81               reffrad(1:ngrid,1:nlayer,iaer) = 2.e-6
82               nueffrad(1:ngrid,1:nlayer,iaer) = 0.1
83            endif
84
85
86
87            if(iaer.gt.5)then
88               print*,'Error in callcorrk, naerkind is too high (>5).'
89               print*,'The code still needs generalisation to arbitrary'
90               print*,'aerosol kinds and number.'
91               call abort
92            endif
93
94         enddo
95
96
97         if (radfixed) then
98
99            write(*,*)"radius of H2O water particles:"
100            rad_h2o=13. ! default value
101            call getin("rad_h2o",rad_h2o)
102            write(*,*)" rad_h2o = ",rad_h2o
103
104            write(*,*)"radius of H2O ice particles:"
105            rad_h2o_ice=35. ! default value
106            call getin("rad_h2o_ice",rad_h2o_ice)
107            write(*,*)" rad_h2o_ice = ",rad_h2o_ice
108
109         else
110
111            write(*,*)"Number mixing ratio of H2O water particles:"
112            Nmix_h2o=1.e6 ! default value
113            call getin("Nmix_h2o",Nmix_h2o)
114            write(*,*)" Nmix_h2o = ",Nmix_h2o
115
116            write(*,*)"Number mixing ratio of H2O ice particles:"
117            Nmix_h2o_ice=Nmix_h2o ! default value
118            call getin("Nmix_h2o_ice",Nmix_h2o_ice)
119            write(*,*)" Nmix_h2o_ice = ",Nmix_h2o_ice
120         endif
121
122      print*,'exit su_aer_radii'
123
124   end subroutine su_aer_radii
125!==================================================================
126
127
128!==================================================================
129   subroutine h2o_reffrad(ngrid,nlayer,pq,pt,reffrad,nueffrad)
130!==================================================================
131!     Purpose
132!     -------
133!     Compute the effective radii of liquid and icy water particles
134!
135!     Authors
136!     -------
137!     Jeremy Leconte (2012)
138!
139!==================================================================
140      use watercommon_h, Only: T_h2O_ice_liq,T_h2O_ice_clouds,rhowater,rhowaterice
141      Implicit none
142
143      include "callkeys.h"
144!      include "dimensions.h"
145!      include "dimphys.h"
146      include "comcstfi.h"
147
148      integer,intent(in) :: ngrid
149      integer,intent(in) :: nlayer
150
151      real, intent(in) :: pq(ngrid,nlayer) !water ice mixing ratios (kg/kg)
152      real, intent(in) :: pt(ngrid,nlayer) !temperature (K)
153      real, intent(out) :: reffrad(ngrid,nlayer)      !aerosol radii
154      real, intent(out) :: nueffrad(ngrid,nlayer) ! dispersion     
155
156      integer :: ig,l
157      real zfice ,zrad,zrad_liq,zrad_ice
158      real,external :: CBRT           
159     
160
161      if (radfixed) then
162         do l=1,nlayer
163            do ig=1,ngrid
164               zfice = 1.0 - (pt(ig,l)-T_h2O_ice_clouds) / (T_h2O_ice_liq-T_h2O_ice_clouds)
165               zfice = MIN(MAX(zfice,0.0),1.0)
166               reffrad(ig,l)= rad_h2o * (1.-zfice) + rad_h2o_ice * zfice
167               nueffrad(ig,l) = coef_chaud * (1.-zfice) + coef_froid * zfice
168            enddo
169         enddo
170      else
171         do l=1,nlayer
172            do ig=1,ngrid
173               zfice = 1.0 - (pt(ig,l)-T_h2O_ice_clouds) / (T_h2O_ice_liq-T_h2O_ice_clouds)
174               zfice = MIN(MAX(zfice,0.0),1.0)
175               zrad_liq  = CBRT( 3*pq(ig,l)/(4*Nmix_h2o*pi*rhowater) )
176               zrad_ice  = CBRT( 3*pq(ig,l)/(4*Nmix_h2o_ice*pi*rhowaterice) )
177               nueffrad(ig,l) = coef_chaud * (1.-zfice) + coef_froid * zfice
178               zrad = zrad_liq * (1.-zfice) + zrad_ice * zfice
179
180               reffrad(ig,l) = min(max(zrad,1.e-6),1000.e-6)
181               enddo
182            enddo     
183      end if
184
185   end subroutine h2o_reffrad
186!==================================================================
187
188
189!==================================================================
190   subroutine h2o_cloudrad(ngrid,nlayer,pql,reffliq,reffice)
191!==================================================================
192!     Purpose
193!     -------
194!     Compute the effective radii of liquid and icy water particles
195!
196!     Authors
197!     -------
198!     Jeremy Leconte (2012)
199!
200!==================================================================
201      use watercommon_h, Only: rhowater,rhowaterice
202      Implicit none
203
204      include "callkeys.h"
205!      include "dimensions.h"
206!      include "dimphys.h"
207      include "comcstfi.h"
208
209      integer,intent(in) :: ngrid
210      integer,intent(in) :: nlayer
211
212      real, intent(in) :: pql(ngrid,nlayer) !condensed water mixing ratios (kg/kg)
213      real, intent(out) :: reffliq(ngrid,nlayer),reffice(ngrid,nlayer)     !liquid and ice water particle radii (m)
214
215      real,external :: CBRT           
216      integer :: i,k
217
218      if (radfixed) then
219         reffliq(1:ngrid,1:nlayer)= rad_h2o
220         reffice(1:ngrid,1:nlayer)= rad_h2o_ice
221      else
222         do k=1,nlayer
223           do i=1,ngrid
224             reffliq(i,k) = CBRT(3*pql(i,k)/(4*Nmix_h2o*pi*rhowater))
225             reffliq(i,k) = min(max(reffliq(i,k),1.e-6),1000.e-6)
226           
227             reffice(i,k) = CBRT(3*pql(i,k)/(4*Nmix_h2o_ice*pi*rhowaterice))
228             reffice(i,k) = min(max(reffice(i,k),1.e-6),1000.e-6)
229           enddo
230         enddo
231      endif
232
233   end subroutine h2o_cloudrad
234!==================================================================
235
236
237
238!==================================================================
239   subroutine co2_reffrad(ngrid,nlayer,nq,pq,reffrad)
240!==================================================================
241!     Purpose
242!     -------
243!     Compute the effective radii of co2 ice particles
244!
245!     Authors
246!     -------
247!     Jeremy Leconte (2012)
248!
249!==================================================================
250      USE tracer_h, only:igcm_co2_ice,rho_co2
251      Implicit none
252
253      include "callkeys.h"
254!      include "dimensions.h"
255!      include "dimphys.h"
256      include "comcstfi.h"
257
258      integer,intent(in) :: ngrid,nlayer,nq
259
260      real, intent(in) :: pq(ngrid,nlayer,nq) !tracer mixing ratios (kg/kg)
261      real, intent(out) :: reffrad(ngrid,nlayer)      !co2 ice particles radii (m)
262
263      integer :: ig,l
264      real :: zrad   
265      real,external :: CBRT           
266           
267     
268
269      if (radfixed) then
270         reffrad(1:ngrid,1:nlayer) = 5.e-5 ! CO2 ice
271      else
272         do l=1,nlayer
273            do ig=1,ngrid
274               zrad = CBRT( 3*pq(ig,l,igcm_co2_ice)/(4*Nmix_co2*pi*rho_co2) )
275               reffrad(ig,l) = min(max(zrad,1.e-6),100.e-6)
276            enddo
277         enddo     
278      end if
279
280   end subroutine co2_reffrad
281!==================================================================
282
283
284
285!==================================================================
286   subroutine dust_reffrad(ngrid,nlayer,reffrad)
287!==================================================================
288!     Purpose
289!     -------
290!     Compute the effective radii of dust particles
291!
292!     Authors
293!     -------
294!     Jeremy Leconte (2012)
295!
296!==================================================================
297      Implicit none
298
299!      include "callkeys.h"
300!      include "dimensions.h"
301!      include "dimphys.h"
302
303      integer,intent(in) :: ngrid
304      integer,intent(in) :: nlayer
305
306      real, intent(out) :: reffrad(ngrid,nlayer)      !dust particles radii (m)
307           
308      reffrad(1:ngrid,1:nlayer) = 2.e-6 ! dust
309
310   end subroutine dust_reffrad
311!==================================================================
312
313
314!==================================================================
315   subroutine h2so4_reffrad(ngrid,nlayer,reffrad)
316!==================================================================
317!     Purpose
318!     -------
319!     Compute the effective radii of h2so4 particles
320!
321!     Authors
322!     -------
323!     Jeremy Leconte (2012)
324!
325!==================================================================
326      Implicit none
327
328!      include "callkeys.h"
329!      include "dimensions.h"
330!      include "dimphys.h"
331
332      integer,intent(in) :: ngrid
333      integer,intent(in) :: nlayer
334
335      real, intent(out) :: reffrad(ngrid,nlayer)      !h2so4 particle radii (m)
336               
337      reffrad(1:ngrid,1:nlayer) = 1.e-6 ! h2so4
338
339   end subroutine h2so4_reffrad
340!==================================================================
341
342!==================================================================
343   subroutine back2lay_reffrad(ngrid,reffrad,nlayer,pplev)
344!==================================================================
345!     Purpose
346!     -------
347!     Compute the effective radii of particles in a 2-layer model
348!
349!     Authors
350!     -------
351!     Sandrine Guerlet (2013)
352!
353!==================================================================
354 
355      use aerosol_mod   !! Particle sizes and boundaries of aerosol layers defined there
356     Implicit none
357
358     include "callkeys.h"
359!     include "dimensions.h"
360!     include "dimphys.h"
361
362      integer,intent(in) :: ngrid
363
364      real, intent(out) :: reffrad(ngrid,nlayer)      ! particle radii (m)
365      REAL,INTENT(IN) :: pplev(ngrid,nlayer+1) ! inter-layer pressure (Pa)
366      INTEGER,INTENT(IN) :: nlayer ! number of atmospheric layers
367      REAL :: expfactor
368      INTEGER l,ig
369           
370      reffrad(:,:)=1e-6  !!initialization, not important
371          DO ig=1,ngrid
372            DO l=1,nlayer-1
373              IF (pplev(ig,l) .le. pres_bottom_tropo .and. pplev(ig,l) .ge. pres_top_tropo) THEN
374                reffrad(ig,l) = size_tropo
375              ELSEIF (pplev(ig,l) .lt. pres_top_tropo .and. pplev(ig,l) .gt. pres_bottom_strato) THEN
376                expfactor=log(size_strato/size_tropo) / log(pres_bottom_strato/pres_top_tropo)
377                reffrad(ig,l)= size_tropo*((pplev(ig,l)/pres_top_tropo)**expfactor)
378              ELSEIF (pplev(ig,l) .le. pres_bottom_strato) then
379                reffrad(ig,l) = size_strato
380              ENDIF
381            ENDDO
382          ENDDO
383
384   end subroutine back2lay_reffrad
385!==================================================================
386
387
388
389end module radii_mod
390!==================================================================
Note: See TracBrowser for help on using the repository browser.