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

Last change on this file since 1579 was 1529, checked in by emillour, 9 years ago

Generic GCM: Towards a cleaner separation between physics and dynamics

  • Got rid of references to "dimensions.h" from physics packages: use nbp_lon (=iim), nbp_lat (=jjp1) and nbp_lev from module mod_grid_phy_lmdz (in phy_common) instead.
  • Removed module "comhdiff_mod.F90", as it is only used by module surf_heat_transp_mod.F90, moved module variables there.
  • Addedin "surf_heat_transp_mod" local versions of some arrays and routines (from dyn3d) required to compute gradient, divergence, etc. on the global dynamics grid. As before, the slab ocean only works in serial.

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