source: trunk/LMDZ.MARS/libf/phymars/updatereffrad.F @ 524

Last change on this file since 524 was 420, checked in by tnavarro, 13 years ago

24/11/11 == TN

corrected minor bug in updatereffrad.F : reffdust was not saved

ccn_factor as not correctly used in sedimentation.

It is now initialized in inifis.F, declared in tracer.h and
used in both simpleclouds.F & callsedim.F to update ice radius.

Commented diagfi outputs in aeropacity.F & improvedclouds.F for non scavenging users.

File size: 6.2 KB
Line 
1      SUBROUTINE updatereffrad(ngrid,nlayer,
2     &                rdust,rice,nuice,
3     &                reffrad,nueffrad,
4     &                pq)
5
6       IMPLICIT NONE
7c=======================================================================
8c   subject:
9c   --------
10c   Subroutine designed to update the aerosol size distribution used by
11c     the radiative transfer scheme. This size distribution is assumed
12c     to be a log-normal distribution, with effective radius "reffrad" and
13c     variance "nueffrad".
14c   At firstcall, "rice" and "nuice" are not known, because
15c     the H2O ice microphysical scheme is called after the radiative
16c     transfer in physiq.F. That's why we assess the size of the
17c     water-ice particles at firstcall (see part 1.2 below).
18c
19c   author:   
20c   ------
21c   J.-B. Madeleine (2009-2010)
22c
23c=======================================================================
24c
25c    Declarations :
26c    -------------
27c
28#include "dimensions.h"
29#include "dimphys.h"
30#include "comcstfi.h"
31#include "callkeys.h"
32#include "dimradmars.h"
33#include "tracer.h"
34#include "aerkind.h"
35#include "yomaer.h"
36
37c-----------------------------------------------------------------------
38c     Inputs:
39c     ------
40
41      INTEGER ngrid,nlayer
42c     Ice geometric mean radius (m)
43      REAL :: rice(ngridmx,nlayermx)
44c     Estimated effective variance of the size distribution (n.u.)
45      REAL :: nuice(ngridmx,nlayermx)
46c     Tracer mass mixing ratio (kg/kg)
47      REAL pq(ngrid,nlayer,nqmx)
48      real rdust(ngridmx,nlayermx) ! Dust geometric mean radius (m)
49
50c     Outputs:
51c     -------
52
53c     Aerosol effective radius used for radiative transfer (meter)
54      REAL :: reffrad(ngridmx,nlayermx,naerkind)
55c     Aerosol effective variance used for radiative transfer (n.u.)
56      REAL :: nueffrad(ngridmx,nlayermx,naerkind)
57
58c     Local variables:
59c     ---------------
60
61      INTEGER :: ig,l          ! 3D grid indices
62      INTEGER :: iaer          ! Aerosol index
63
64c     Number of cloud condensation nuclei near the surface
65c     (only used at firstcall). This value is taken from
66c     Montmessin et al. 2004 JGR 109 E10004 p5 (2E6 part m-3), and
67c     converted to part kg-1 using a typical atmospheric density.
68
69      REAL, PARAMETER :: ccn0 = 1.3E8
70
71      LOGICAL firstcall
72      DATA firstcall/.true./
73      SAVE firstcall
74
75      REAL CBRT
76      EXTERNAL CBRT
77
78      REAL,SAVE :: nueffdust(ngridmx,nlayermx) ! Dust effective variance
79
80c     Local saved variables:
81c     ---------------------
82
83c==================================================================
84
85      IF (firstcall) THEN
86c       At firstcall, rdust and rice are not known; therefore
87c         they need to be computed below.
88
89c       1.1 Dust particles
90c       ------------------
91        IF (doubleq.AND.active) THEN
92          DO l=1,nlayer
93            DO ig=1, ngrid
94              rdust(ig,l) =
95     &          CBRT(r3n_q*pq(ig,l,igcm_dust_mass)/
96     &          max(pq(ig,l,igcm_dust_number),0.01))
97              rdust(ig,l)=min(max(rdust(ig,l),1.e-10),500.e-6)
98              nueffdust(ig,l) = exp(varian**2.)-1.
99             ENDDO
100           ENDDO
101        ELSE
102          DO l=1,nlayer
103            DO ig=1, ngrid
104              rdust(ig,l) = 0.8E-6
105              nueffdust(ig,l) = 0.3
106            ENDDO
107          ENDDO
108        ENDIF
109c       1.2 Water-ice particles
110c       -----------------------
111        IF (water.AND.activice) THEN
112          DO l=1,nlayer
113            DO ig=1,ngrid
114              rice(ig,l) = max( CBRT(
115     &          (pq(ig,l,igcm_h2o_ice)/rho_ice +
116     &          ccn0*(4./3.)*pi*rdust(ig,l)**3.) /
117     &          (ccn0*4./3.*pi)),rdust(ig,l) )
118              nuice(ig,l) = nuice_ref
119            ENDDO
120          ENDDO
121        ENDIF ! of if (water.AND.activice)
122        firstcall = .false.
123      ENDIF ! of if firstcall
124
125c==================================================================
126c 2. Radius used in the radiative transfer code (reffrad)
127c==================================================================
128
129      DO iaer = 1, naerkind ! Loop on aerosol kind
130        aerkind: SELECT CASE (name_iaer(iaer))
131c==================================================================
132        CASE("dust_conrath") aerkind         ! Typical dust profile
133c==================================================================
134          DO l=1,nlayer
135            DO ig=1,ngrid
136              reffrad(ig,l,iaer) = rdust(ig,l) *
137     &          (1.e0 + nueffdust(ig,l))**2.5
138              nueffrad(ig,l,iaer) = nueffdust(ig,l)
139            ENDDO
140          ENDDO
141c==================================================================
142        CASE("dust_doubleq") aerkind! Two-moment scheme for dust
143c==================================================================
144          DO l=1,nlayer
145            DO ig=1,ngrid
146              reffrad(ig,l,iaer) = rdust(ig,l) * ref_r0
147              nueffrad(ig,l,iaer) = nueffdust(ig,l)
148            ENDDO
149          ENDDO
150c==================================================================
151        CASE("dust_submicron") aerkind   ! Small dust population
152c==================================================================
153          DO l=1,nlayer
154            DO ig=1,ngrid
155              reffrad(ig,l,iaer)=radius(igcm_dust_submicron)
156              nueffrad(ig,l,iaer)=0.03
157            ENDDO
158          ENDDO     
159c==================================================================
160        CASE("h2o_ice") aerkind             ! Water ice crystals
161c==================================================================
162          DO l=1,nlayer
163            DO ig=1,ngrid
164c             About reffice, do not confuse the mass mean radius
165c             (rayon moyen massique) and the number median radius
166c             (or geometric mean radius, rayon moyen géométrique).
167c             rice is a mass mean radius, whereas rdust
168c             is a geometric mean radius:
169c             number median rad = mass mean rad x exp(-1.5 sigma0^2)
170c             (Montmessin et al. 2004 paragraph 30). Therefore:
171              reffrad(ig,l,iaer)=rice(ig,l)*(1.+nuice_ref)
172              nueffrad(ig,l,iaer)=nuice_ref
173            ENDDO
174          ENDDO
175c==================================================================
176        END SELECT aerkind
177      ENDDO ! iaer (loop on aerosol kind)
178
179      RETURN
180      END
Note: See TracBrowser for help on using the repository browser.