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

Last change on this file since 918 was 863, checked in by jleconte, 13 years ago

23/01/2013 == JL

  • Correction in largescale. a rneb factor was forgotten
  • Added some spectra in ave_stelpec
  • Corrected reevaporation in rain. Now conserve water better


File size: 10.0 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,pq,pt,reffrad,nueffrad)
122!==================================================================
123!     Purpose
124!     -------
125!     Compute the effective radii of liquid and icy water particles
126!
127!     Authors
128!     -------
129!     Jeremy Leconte (2012)
130!
131!==================================================================
132      use watercommon_h, Only: T_h2O_ice_liq,T_h2O_ice_clouds,rhowater,rhowaterice
133      Implicit none
134
135#include "callkeys.h"
136#include "dimensions.h"
137#include "dimphys.h"
138#include "comcstfi.h"
139
140      integer,intent(in) :: ngrid
141
142      real, intent(in) :: pq(ngrid,nlayermx) !water ice mixing ratios (kg/kg)
143      real, intent(in) :: pt(ngrid,nlayermx) !temperature (K)
144      real, intent(out) :: reffrad(ngrid,nlayermx)      !aerosol radii
145      real, intent(out) :: nueffrad(ngrid,nlayermx) ! dispersion     
146
147      integer :: ig,l
148      real zfice ,zrad,zrad_liq,zrad_ice
149      real,external :: CBRT           
150     
151
152      if (radfixed) then
153         do l=1,nlayermx
154            do ig=1,ngrid
155               zfice = 1.0 - (pt(ig,l)-T_h2O_ice_clouds) / (T_h2O_ice_liq-T_h2O_ice_clouds)
156               zfice = MIN(MAX(zfice,0.0),1.0)
157               reffrad(ig,l)= rad_h2o * (1.-zfice) + rad_h2o_ice * zfice
158               nueffrad(ig,l) = coef_chaud * (1.-zfice) + coef_froid * zfice
159            enddo
160         enddo
161      else
162         do l=1,nlayermx
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               zrad_liq  = CBRT( 3*pq(ig,l)/(4*Nmix_h2o*pi*rhowater) )
167               zrad_ice  = CBRT( 3*pq(ig,l)/(4*Nmix_h2o_ice*pi*rhowaterice) )
168               nueffrad(ig,l) = coef_chaud * (1.-zfice) + coef_froid * zfice
169               zrad = zrad_liq * (1.-zfice) + zrad_ice * zfice
170
171               reffrad(ig,l) = min(max(zrad,1.e-6),1000.e-6)
172               enddo
173            enddo     
174      end if
175
176   end subroutine h2o_reffrad
177!==================================================================
178
179
180!==================================================================
181   subroutine h2o_cloudrad(ngrid,pql,reffliq,reffice)
182!==================================================================
183!     Purpose
184!     -------
185!     Compute the effective radii of liquid and icy water particles
186!
187!     Authors
188!     -------
189!     Jeremy Leconte (2012)
190!
191!==================================================================
192      use watercommon_h, Only: rhowater,rhowaterice
193      Implicit none
194
195#include "callkeys.h"
196#include "dimensions.h"
197#include "dimphys.h"
198#include "comcstfi.h"
199
200      integer,intent(in) :: ngrid
201
202      real, intent(in) :: pql(ngrid,nlayermx) !condensed water mixing ratios (kg/kg)
203      real, intent(out) :: reffliq(ngrid,nlayermx),reffice(ngrid,nlayermx)     !liquid and ice water particle radii (K)
204
205      real,external :: CBRT           
206     
207
208      if (radfixed) then
209         reffliq(1:ngrid,1:nlayermx)= rad_h2o
210         reffice(1:ngrid,1:nlayermx)= rad_h2o_ice
211      else
212         reffliq(1:ngrid,1:nlayermx)  = CBRT( 3*pql(1:ngrid,1:nlayermx)/(4*Nmix_h2o*pi*rhowater) )
213         reffliq(1:ngrid,1:nlayermx)  = min(max(reffliq(1:ngrid,1:nlayermx),1.e-6),1000.e-6)
214         reffice(1:ngrid,1:nlayermx)  = CBRT( 3*pql(1:ngrid,1:nlayermx)/(4*Nmix_h2o_ice*pi*rhowaterice) )
215         reffice(1:ngrid,1:nlayermx)  = min(max(reffice(1:ngrid,1:nlayermx),1.e-6),1000.e-6)
216      end if
217
218   end subroutine h2o_cloudrad
219!==================================================================
220
221
222
223!==================================================================
224   subroutine co2_reffrad(ngrid,nq,pq,reffrad)
225!==================================================================
226!     Purpose
227!     -------
228!     Compute the effective radii of co2 ice particles
229!
230!     Authors
231!     -------
232!     Jeremy Leconte (2012)
233!
234!==================================================================
235      USE tracer_h, only:igcm_co2_ice,rho_co2
236      Implicit none
237
238#include "callkeys.h"
239#include "dimensions.h"
240#include "dimphys.h"
241#include "comcstfi.h"
242
243      integer,intent(in) :: ngrid,nq
244
245      real, intent(in) :: pq(ngrid,nlayermx,nq) !tracer mixing ratios (kg/kg)
246      real, intent(out) :: reffrad(ngrid,nlayermx)      !co2 ice particles radii (K)
247
248      integer :: ig,l
249      real :: zrad   
250      real,external :: CBRT           
251           
252     
253
254      if (radfixed) then
255         reffrad(1:ngrid,1:nlayermx) = 5.e-5 ! CO2 ice
256      else
257         do l=1,nlayermx
258            do ig=1,ngrid
259               zrad = CBRT( 3*pq(ig,l,igcm_co2_ice)/(4*Nmix_co2*pi*rho_co2) )
260               reffrad(ig,l) = min(max(zrad,1.e-6),100.e-6)
261            enddo
262         enddo     
263      end if
264
265   end subroutine co2_reffrad
266!==================================================================
267
268
269
270!==================================================================
271   subroutine dust_reffrad(ngrid,reffrad)
272!==================================================================
273!     Purpose
274!     -------
275!     Compute the effective radii of dust particles
276!
277!     Authors
278!     -------
279!     Jeremy Leconte (2012)
280!
281!==================================================================
282      Implicit none
283
284#include "callkeys.h"
285#include "dimensions.h"
286#include "dimphys.h"
287
288      integer,intent(in) :: ngrid
289
290      real, intent(out) :: reffrad(ngrid,nlayermx)      !dust particles radii (K)
291           
292      reffrad(1:ngrid,1:nlayermx) = 2.e-6 ! dust
293
294   end subroutine dust_reffrad
295!==================================================================
296
297
298!==================================================================
299   subroutine h2so4_reffrad(ngrid,reffrad)
300!==================================================================
301!     Purpose
302!     -------
303!     Compute the effective radii of h2so4 particles
304!
305!     Authors
306!     -------
307!     Jeremy Leconte (2012)
308!
309!==================================================================
310      Implicit none
311
312#include "callkeys.h"
313#include "dimensions.h"
314#include "dimphys.h"
315
316      integer,intent(in) :: ngrid
317
318      real, intent(out) :: reffrad(ngrid,nlayermx)      !h2so4 particle radii (K)
319               
320      reffrad(1:ngrid,1:nlayermx) = 1.e-6 ! h2so4
321
322   end subroutine h2so4_reffrad
323!==================================================================
324
325
326
327end module radii_mod
328!==================================================================
Note: See TracBrowser for help on using the repository browser.