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

Last change on this file since 858 was 858, checked in by emillour, 13 years ago

Generic GCM:

  • Fixed sedimentation issue: ensure in callsedim that the correct radii are provided to newsedim and also that the updated temperature and tracer mixing ratios are used to compute sedimentation.
  • Updated the way aerosol radii are considered and used; routines in radii_mod (h2o_reffrad, co2_reffrad, etc.) only handle a single aerosol. The idea here is that these can be called from anywhere and that the caller doesn't need to have the full (naerkind size) array of aerosol radii.
  • cleanup (addition of intent(..) to routine arguments) in various routines

EM

File size: 11.7 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,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
46      real, intent(out) :: reffrad(ngrid,nlayermx,naerkind)      !aerosols radii (K)
47      real, intent(out) :: nueffrad(ngrid,nlayermx,naerkind)     !variance     
48
49      logical, save :: firstcall=.true.
50      integer :: iaer   
51     
52      print*,'enter su_aer_radii'
53          do iaer=1,naerkind
54!     these values will change once the microphysics gets to work
55!     UNLESS tracer=.false., in which case we should be working with
56!     a fixed aerosol layer, and be able to define reffrad in a
57!     .def file. To be improved!
58
59            if(iaer.eq.iaero_co2)then ! CO2 ice
60               reffrad(1:ngrid,1:nlayermx,iaer) = 1.e-4
61               nueffrad(1:ngrid,1:nlayermx,iaer) = 0.1
62            endif
63
64            if(iaer.eq.iaero_h2o)then ! H2O ice
65               reffrad(1:ngrid,1:nlayermx,iaer) = 1.e-5
66               nueffrad(1:ngrid,1:nlayermx,iaer) = 0.1
67            endif
68
69            if(iaer.eq.iaero_dust)then ! dust
70               reffrad(1:ngrid,1:nlayermx,iaer) = 1.e-5
71               nueffrad(1:ngrid,1:nlayermx,iaer) = 0.1
72            endif
73 
74            if(iaer.eq.iaero_h2so4)then ! H2O ice
75               reffrad(1:ngrid,1:nlayermx,iaer) = 1.e-6
76               nueffrad(1:ngrid,1:nlayermx,iaer) = 0.1
77            endif
78
79            if(iaer.gt.4)then
80               print*,'Error in callcorrk, naerkind is too high (>4).'
81               print*,'The code still needs generalisation to arbitrary'
82               print*,'aerosol kinds and number.'
83               call abort
84            endif
85
86         enddo
87
88
89         if (radfixed) then
90
91            write(*,*)"radius of H2O water particles:"
92            rad_h2o=13. ! default value
93            call getin("rad_h2o",rad_h2o)
94            write(*,*)" rad_h2o = ",rad_h2o
95
96            write(*,*)"radius of H2O ice particles:"
97            rad_h2o_ice=35. ! default value
98            call getin("rad_h2o_ice",rad_h2o_ice)
99            write(*,*)" rad_h2o_ice = ",rad_h2o_ice
100
101         else
102
103            write(*,*)"Number mixing ratio of H2O water particles:"
104            Nmix_h2o=1.e6 ! default value
105            call getin("Nmix_h2o",Nmix_h2o)
106            write(*,*)" Nmix_h2o = ",Nmix_h2o
107
108            write(*,*)"Number mixing ratio of H2O ice particles:"
109            Nmix_h2o_ice=Nmix_h2o ! default value
110            call getin("Nmix_h2o_ice",Nmix_h2o_ice)
111            write(*,*)" Nmix_h2o_ice = ",Nmix_h2o_ice
112         endif
113
114      print*,'exit su_aer_radii'
115
116   end subroutine su_aer_radii
117!==================================================================
118
119
120!==================================================================
121!   subroutine h2o_reffrad(ngrid,nq,pq,pt,reffrad,nueffrad)
122   subroutine h2o_reffrad(ngrid,pq,pt,reffrad,nueffrad)
123!==================================================================
124!     Purpose
125!     -------
126!     Compute the effective radii of liquid and icy water particles
127!
128!     Authors
129!     -------
130!     Jeremy Leconte (2012)
131!
132!==================================================================
133!      use radinc_h, only: naerkind
134      use watercommon_h, Only: T_h2O_ice_liq,T_h2O_ice_clouds,rhowater,rhowaterice
135!      use aerosol_mod, only : iaero_h2o
136!      USE tracer_h, only: igcm_h2o_ice
137      Implicit none
138
139#include "callkeys.h"
140#include "dimensions.h"
141#include "dimphys.h"
142#include "comcstfi.h"
143
144      integer,intent(in) :: ngrid
145!      intent,integer(in) :: nq
146
147!      real, intent(in) :: pq(ngrid,nlayermx,nq) !tracer mixing ratios (kg/kg)
148      real, intent(in) :: pq(ngrid,nlayermx) !water ice mixing ratios (kg/kg)
149      real, intent(in) :: pt(ngrid,nlayermx) !temperature (K)
150      real, intent(out) :: reffrad(ngrid,nlayermx)      !aerosol radii
151!      real, intent(out) :: reffrad(ngrid,nlayermx,naerkind)      !aerosols radii
152      real, intent(out) :: nueffrad(ngrid,nlayermx) ! dispersion     
153!      real, intent(out) :: nueffrad(ngrid,nlayermx,naerkind) ! dispersion     
154
155      integer :: ig,l
156      real zfice ,zrad,zrad_liq,zrad_ice
157      real,external :: CBRT           
158     
159
160      if (radfixed) then
161         do l=1,nlayermx
162            do ig=1,ngrid
163               zfice = 1.0 - (pt(ig,l)-T_h2O_ice_clouds) / (T_h2O_ice_liq-T_h2O_ice_clouds)
164               zfice = MIN(MAX(zfice,0.0),1.0)
165!               reffrad(ig,l,iaero_h2o)= rad_h2o * (1.-zfice) + rad_h2o_ice * zfice
166               reffrad(ig,l)= rad_h2o * (1.-zfice) + rad_h2o_ice * zfice
167!               nueffrad(ig,l,iaero_h2o) = coef_chaud * (1.-zfice) + coef_froid * zfice
168               nueffrad(ig,l) = coef_chaud * (1.-zfice) + coef_froid * zfice
169            enddo
170         enddo
171      else
172         do l=1,nlayermx
173            do ig=1,ngrid
174               zfice = 1.0 - (pt(ig,l)-T_h2O_ice_clouds) / (T_h2O_ice_liq-T_h2O_ice_clouds)
175               zfice = MIN(MAX(zfice,0.0),1.0)
176!              zrad_liq  = CBRT( 3*pq(ig,l,igcm_h2o_ice)/(4*Nmix_h2o*pi*rhowater) )
177               zrad_liq  = CBRT( 3*pq(ig,l)/(4*Nmix_h2o*pi*rhowater) )
178!              zrad_ice  = CBRT( 3*pq(ig,l,igcm_h2o_ice)/(4*Nmix_h2o_ice*pi*rhowaterice) )
179               zrad_ice  = CBRT( 3*pq(ig,l)/(4*Nmix_h2o_ice*pi*rhowaterice) )
180!               nueffrad(ig,l,iaero_h2o) = coef_chaud * (1.-zfice) + coef_froid * zfice
181               nueffrad(ig,l) = coef_chaud * (1.-zfice) + coef_froid * zfice
182               zrad = zrad_liq * (1.-zfice) + zrad_ice * zfice
183!              reffrad(ig,l,iaero_h2o) = min(max(zrad,1.e-6),100.e-6)
184               reffrad(ig,l) = min(max(zrad,1.e-6),100.e-6)
185               enddo
186            enddo     
187      end if
188
189   end subroutine h2o_reffrad
190!==================================================================
191
192
193!==================================================================
194   subroutine h2o_cloudrad(ngrid,pql,reffliq,reffice)
195!==================================================================
196!     Purpose
197!     -------
198!     Compute the effective radii of liquid and icy water particles
199!
200!     Authors
201!     -------
202!     Jeremy Leconte (2012)
203!
204!==================================================================
205      use watercommon_h, Only: rhowater,rhowaterice
206!      USE tracer_h
207      Implicit none
208
209#include "callkeys.h"
210#include "dimensions.h"
211#include "dimphys.h"
212#include "comcstfi.h"
213
214      integer,intent(in) :: ngrid
215
216      real, intent(in) :: pql(ngrid,nlayermx) !condensed water mixing ratios (kg/kg)
217      real, intent(out) :: reffliq(ngrid,nlayermx),reffice(ngrid,nlayermx)     !liquid and ice water particle radii (K)
218
219      real,external :: CBRT           
220     
221
222      if (radfixed) then
223         reffliq(1:ngrid,1:nlayermx)= rad_h2o
224         reffice(1:ngrid,1:nlayermx)= rad_h2o_ice
225      else
226         reffliq(1:ngrid,1:nlayermx)  = CBRT( 3*pql(1:ngrid,1:nlayermx)/(4*Nmix_h2o*pi*rhowater) )
227         reffliq(1:ngrid,1:nlayermx)  = min(max(reffliq(1:ngrid,1:nlayermx),1.e-6),100.e-6)
228         reffice(1:ngrid,1:nlayermx)  = CBRT( 3*pql(1:ngrid,1:nlayermx)/(4*Nmix_h2o_ice*pi*rhowaterice) )
229         reffice(1:ngrid,1:nlayermx)  = min(max(reffice(1:ngrid,1:nlayermx),1.e-6),100.e-6)
230      end if
231
232   end subroutine h2o_cloudrad
233!==================================================================
234
235
236
237!==================================================================
238   subroutine co2_reffrad(ngrid,nq,pq,reffrad)
239!==================================================================
240!     Purpose
241!     -------
242!     Compute the effective radii of co2 ice particles
243!
244!     Authors
245!     -------
246!     Jeremy Leconte (2012)
247!
248!==================================================================
249!      use radinc_h, only: naerkind
250!      use aerosol_mod, only : iaero_co2
251      USE tracer_h, only:igcm_co2_ice,rho_co2
252      Implicit none
253
254#include "callkeys.h"
255#include "dimensions.h"
256#include "dimphys.h"
257#include "comcstfi.h"
258
259      integer,intent(in) :: ngrid,nq
260
261      real, intent(in) :: pq(ngrid,nlayermx,nq) !tracer mixing ratios (kg/kg)
262!      real, intent(out) :: reffrad(ngrid,nlayermx,naerkind)      !aerosols radii (K)
263      real, intent(out) :: reffrad(ngrid,nlayermx)      !aerosols radii (K)
264
265      integer :: ig,l
266      real :: zrad   
267      real,external :: CBRT           
268           
269     
270
271      if (radfixed) then
272!         reffrad(1:ngrid,1:nlayermx,iaero_co2) = 5.e-5 ! CO2 ice
273         reffrad(1:ngrid,1:nlayermx) = 5.e-5 ! CO2 ice
274      else
275         do l=1,nlayermx
276            do ig=1,ngrid
277               zrad = CBRT( 3*pq(ig,l,igcm_co2_ice)/(4*Nmix_co2*pi*rho_co2) )
278!               reffrad(ig,l,iaero_co2) = min(max(zrad,1.e-6),100.e-6)
279               reffrad(ig,l) = min(max(zrad,1.e-6),100.e-6)
280            enddo
281         enddo     
282      end if
283
284   end subroutine co2_reffrad
285!==================================================================
286
287
288
289!==================================================================
290   subroutine dust_reffrad(ngrid,reffrad)
291!==================================================================
292!     Purpose
293!     -------
294!     Compute the effective radii of dust particles
295!
296!     Authors
297!     -------
298!     Jeremy Leconte (2012)
299!
300!==================================================================
301!      use radinc_h, only: naerkind
302!      use aerosol_mod, only : iaero_dust
303      Implicit none
304
305#include "callkeys.h"
306#include "dimensions.h"
307#include "dimphys.h"
308
309      integer,intent(in) :: ngrid
310
311!      real, intent(out) :: reffrad(ngrid,nlayermx,naerkind)      !aerosols radii (K)
312      real, intent(out) :: reffrad(ngrid,nlayermx)      !aerosols radii (K)
313           
314!      reffrad(1:ngrid,1:nlayermx,iaero_dust) = 2.e-6 ! dust
315      reffrad(1:ngrid,1:nlayermx) = 2.e-6 ! dust
316
317   end subroutine dust_reffrad
318!==================================================================
319
320
321!==================================================================
322   subroutine h2so4_reffrad(ngrid,reffrad)
323!==================================================================
324!     Purpose
325!     -------
326!     Compute the effective radii of h2so4 particles
327!
328!     Authors
329!     -------
330!     Jeremy Leconte (2012)
331!
332!==================================================================
333!      use radinc_h, only: naerkind
334!      use aerosol_mod, only : iaero_h2so4
335      Implicit none
336
337#include "callkeys.h"
338#include "dimensions.h"
339#include "dimphys.h"
340
341      integer,intent(in) :: ngrid
342
343!      real, intent(out) :: reffrad(ngrid,nlayermx,naerkind)      !aerosols radii (K)
344      real, intent(out) :: reffrad(ngrid,nlayermx)      !aerosols radii (K)
345               
346!      reffrad(1:ngrid,1:nlayermx,iaero_h2so4) = 1.e-6 ! h2so4
347      reffrad(1:ngrid,1:nlayermx) = 1.e-6 ! h2so4
348
349   end subroutine h2so4_reffrad
350!==================================================================
351
352
353
354end module radii_mod
355!==================================================================
Note: See TracBrowser for help on using the repository browser.