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

Last change on this file since 773 was 728, checked in by jleconte, 12 years ago

18/07/2012 == JL

  • New water cycle scheme:
    • largescale now in F90. Robustness increased by i) including evap inside largescale ii) computing the

condensed water amount iteratively

  • same improvements in moistadj.
  • Water thermodynamical data and saturation curves centralized in module watercommn_h
    • The saturation curves used are now Tetens formula as they are analyticaly inversible (Ts(P)-> Ps(T)).

New saturation curve yields very good agreement with the former one.

  • Saturation curves are now generalized for arbitrary water amount (not just q<<1)
  • The old watersat should be removed soon.
  • The effect of water vapor on total (surface) pressure can be taken into account by setting

mass_redistrib=.true. in callphys.def (routine mass_redistribution inspired from co2_condense in martian
model but with a different scheme as many routines evaporate/condense water vapor).

  • New cloud and precipitation scheme (JL + BC):
    • The default recovery assumption for computing the total cloud fraction has been changed (total random gave too

large cloud fractions). See totalcloudfrac.F90 for details and to change this.

  • Totalcloudfraction now set the total cloud fraction to the fraction of the

optically thickest cloud and totalcloudfrac is thus called in aeropacity.

  • Only the total cloud fraction is used to compute optical depth in aeropacity (no more effective

optical depth with exponential formula).

  • 4 precipitation schemes are now available (see rain.F90 for details). The choice can be made using precip_scheme

in callphys.def. Usage of the more physically based model of Boucher et al 95 (precip_scheme=4) is recommended.
default behavior is set to the former "simple scheme" (precip_scheme=1).

  • See rain.f90 to determine the parameter to be defined in callphys.def as a function of the precipitation scheme used.
  • Physiq.F90 now written in a matricial (more F90) way.
  • Radii (H2O and CO2 cloud particles, aerosols, duts, ...) calculations now centralized in module radii_mod.F90

and work with the new aerosol scheme implemented by Laura K. Some inconsistency may remain in callsedim.


Implementation compiled with ifort and pgf90.
gcm.e runs in Earth and Early Mars case with CO2 and H2O cycle + dust.

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