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

Last change on this file since 744 was 744, checked in by tnavarro, 12 years ago

forgot updatereffrad in commit 740

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