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

Last change on this file since 706 was 633, checked in by tnavarro, 13 years ago

last scheme in commit r626 led to a wrong physical behaviour. This version uses a new subtimestep for microphysics that should be faster than the last one.

File size: 7.6 KB
Line 
1      SUBROUTINE updatereffrad(ngrid,nlayer,
2     &                rdust,rice,nuice,
3     &                reffrad,nueffrad,
4     &                pq,tauscaling)
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     
71c     For microphysics only:     
72      REAL Mo,No                       ! Mass and number of ccn
73      REAL rhocloud(ngridmx,nlayermx)  ! Cloud density (kg.m-3)
74      REAL tauscaling(ngridmx)         ! Convertion factor for qccn and Nccn
75
76      LOGICAL firstcall
77      DATA firstcall/.true./
78      SAVE firstcall
79
80      REAL CBRT
81      EXTERNAL CBRT
82
83      REAL,SAVE :: nueffdust(ngridmx,nlayermx) ! Dust effective variance
84
85c     Local saved variables:
86c     ---------------------
87
88
89c==================================================================
90c 1. Update radius from fields from dynamics or initial state
91c==================================================================
92
93c       1.1 Dust particles
94c       ------------------
95        IF (doubleq.AND.active) THEN
96          DO l=1,nlayer
97            DO ig=1, ngrid
98              rdust(ig,l) =
99     &          CBRT(r3n_q*pq(ig,l,igcm_dust_mass)/
100     &          max(pq(ig,l,igcm_dust_number),0.01))
101              rdust(ig,l)=min(max(rdust(ig,l),1.e-10),500.e-6)
102              nueffdust(ig,l) = exp(varian**2.)-1.
103             ENDDO
104           ENDDO
105        ELSE
106          DO l=1,nlayer
107            DO ig=1, ngrid
108              rdust(ig,l) = 0.8E-6
109              nueffdust(ig,l) = 0.3
110            ENDDO
111          ENDDO
112        ENDIF
113       
114c       1.2 Water-ice particles
115c       -----------------------
116        IF (water.AND.activice) THEN         
117          IF ((firstcall).or.(microphys.eqv..false.)) THEN
118            DO l=1,nlayer
119              DO ig=1,ngrid
120                rice(ig,l) = max(CBRT(
121     &            (pq(ig,l,igcm_h2o_ice)/rho_ice +
122     &            ccn0*(4./3.)*pi*rdust(ig,l)**3.) /
123     &            (ccn0*4./3.*pi)),rdust(ig,l) )
124                rice(ig,l)=min(max(rice(ig,l),1.e-10),500.e-6)
125                nuice(ig,l) = nuice_ref
126              ENDDO
127            ENDDO
128          firstcall = .false.
129c    At firstcall, the true number and true mass of cloud condensation nuclei are not known.
130c    Indeed it is scaled on the prescribed dust opacity via a 'tauscaling' coefficient
131c    computed after radiative transfer.
132c    Therefore, we use a typical value ccn0 at firstcall, like it is done without microphysics.
133          ELSE
134            DO l=1,nlayer
135              DO ig=1,ngrid
136                Mo = pq(ig,l,igcm_h2o_ice) +
137     &              pq(ig,l,igcm_ccn_mass)* tauscaling(ig) + 1.e-30
138                No = pq(ig,l,igcm_ccn_number)* tauscaling(ig)+ 1e-30
139                rhocloud(ig,l) =  pq(ig,l,igcm_h2o_ice)*rho_ice / Mo
140     &           + pq(ig,l,igcm_ccn_mass)*tauscaling(ig)*rho_dust/Mo
141                rhocloud(ig,l) =
142     &            min(max(rhocloud(ig,l),rho_ice),rho_dust)
143                rice(ig,l) =
144     &           CBRT( Mo/No * 0.75 / pi / rhocloud(ig,l))
145                rice(ig,l)=min(max(rice(ig,l),1.e-10),500.e-6)
146                nuice(ig,l) = nuice_ref
147              ENDDO
148            ENDDO
149          ENDIF ! of if ((firstcall).or.(microphys.eq.false))
150        ENDIF ! of if (water.AND.activice)
151       
152
153c==================================================================
154c 2. Radius used in the radiative transfer code (reffrad)
155c==================================================================
156
157      DO iaer = 1, naerkind ! Loop on aerosol kind
158        aerkind: SELECT CASE (name_iaer(iaer))
159c==================================================================
160        CASE("dust_conrath") aerkind         ! Typical dust profile
161c==================================================================
162          DO l=1,nlayer
163            DO ig=1,ngrid
164              reffrad(ig,l,iaer) = rdust(ig,l) *
165     &          (1.e0 + nueffdust(ig,l))**2.5
166              nueffrad(ig,l,iaer) = nueffdust(ig,l)
167            ENDDO
168          ENDDO
169c==================================================================
170        CASE("dust_doubleq") aerkind! Two-moment scheme for dust
171c==================================================================
172          DO l=1,nlayer
173            DO ig=1,ngrid
174              reffrad(ig,l,iaer) = rdust(ig,l) * ref_r0
175              nueffrad(ig,l,iaer) = nueffdust(ig,l)
176            ENDDO
177          ENDDO
178c==================================================================
179        CASE("dust_submicron") aerkind   ! Small dust population
180c==================================================================
181          DO l=1,nlayer
182            DO ig=1,ngrid
183              reffrad(ig,l,iaer)=radius(igcm_dust_submicron)
184              nueffrad(ig,l,iaer)=0.03
185            ENDDO
186          ENDDO     
187c==================================================================
188        CASE("h2o_ice") aerkind             ! Water ice crystals
189c==================================================================
190          DO l=1,nlayer
191            DO ig=1,ngrid
192c             About reffice, do not confuse the mass mean radius
193c             (rayon moyen massique) and the number median radius
194c             (or geometric mean radius, rayon moyen géométrique).
195c             rice is a mass mean radius, whereas rdust
196c             is a geometric mean radius:
197c             number median rad = mass mean rad x exp(-1.5 sigma0^2)
198c             (Montmessin et al. 2004 paragraph 30). Therefore:
199              reffrad(ig,l,iaer)=rice(ig,l)*(1.+nuice_ref)
200              nueffrad(ig,l,iaer)=nuice_ref
201            ENDDO
202          ENDDO
203c==================================================================
204        END SELECT aerkind
205      ENDDO ! iaer (loop on aerosol kind)
206
207      RETURN
208      END
Note: See TracBrowser for help on using the repository browser.