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

Last change on this file since 627 was 626, checked in by tnavarro, 13 years ago

New scheme for the clouds, no more sub-timestep. Clouds sedimentation is done with the dust one in callsedim.F like it was before. Added latent heat for sublimating ground ice. Bugs corrected. THIS VERSION OF THE WATER CYCLE SHOULD NOT BE USED WITH THERMALS DUE TO NEGATIVE TRACERS ISSUES.

File size: 6.3 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
71c      LOGICAL firstcall
72c      DATA firstcall/.true./
73c      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
85c      IF (firstcall) THEN
86c       At firstcall, rdust and rice are not known; therefore
87c         they need to be computed below.
88
89c      Correction TN 17/04: rdust and rice must be updated at all steps,
90c      otherwise it is a possible source of bugs
91
92c       1.1 Dust particles
93c       ------------------
94        IF (doubleq.AND.active) THEN
95          DO l=1,nlayer
96            DO ig=1, ngrid
97              rdust(ig,l) =
98     &          CBRT(r3n_q*pq(ig,l,igcm_dust_mass)/
99     &          max(pq(ig,l,igcm_dust_number),0.01))
100              rdust(ig,l)=min(max(rdust(ig,l),1.e-10),500.e-6)
101              nueffdust(ig,l) = exp(varian**2.)-1.
102             ENDDO
103           ENDDO
104        ELSE
105          DO l=1,nlayer
106            DO ig=1, ngrid
107              rdust(ig,l) = 0.8E-6
108              nueffdust(ig,l) = 0.3
109            ENDDO
110          ENDDO
111        ENDIF
112c       1.2 Water-ice particles
113c       -----------------------
114        IF (water.AND.activice) THEN
115          DO l=1,nlayer
116            DO ig=1,ngrid
117              rice(ig,l) = max( CBRT(
118     &          (pq(ig,l,igcm_h2o_ice)/rho_ice +
119     &          ccn0*(4./3.)*pi*rdust(ig,l)**3.) /
120     &          (ccn0*4./3.*pi)),rdust(ig,l) )
121              nuice(ig,l) = nuice_ref
122            ENDDO
123          ENDDO
124        ENDIF ! of if (water.AND.activice)
125       
126c        firstcall = .false.
127c      ENDIF ! of if firstcall
128
129c==================================================================
130c 2. Radius used in the radiative transfer code (reffrad)
131c==================================================================
132
133      DO iaer = 1, naerkind ! Loop on aerosol kind
134        aerkind: SELECT CASE (name_iaer(iaer))
135c==================================================================
136        CASE("dust_conrath") aerkind         ! Typical dust profile
137c==================================================================
138          DO l=1,nlayer
139            DO ig=1,ngrid
140              reffrad(ig,l,iaer) = rdust(ig,l) *
141     &          (1.e0 + nueffdust(ig,l))**2.5
142              nueffrad(ig,l,iaer) = nueffdust(ig,l)
143            ENDDO
144          ENDDO
145c==================================================================
146        CASE("dust_doubleq") aerkind! Two-moment scheme for dust
147c==================================================================
148          DO l=1,nlayer
149            DO ig=1,ngrid
150              reffrad(ig,l,iaer) = rdust(ig,l) * ref_r0
151              nueffrad(ig,l,iaer) = nueffdust(ig,l)
152            ENDDO
153          ENDDO
154c==================================================================
155        CASE("dust_submicron") aerkind   ! Small dust population
156c==================================================================
157          DO l=1,nlayer
158            DO ig=1,ngrid
159              reffrad(ig,l,iaer)=radius(igcm_dust_submicron)
160              nueffrad(ig,l,iaer)=0.03
161            ENDDO
162          ENDDO     
163c==================================================================
164        CASE("h2o_ice") aerkind             ! Water ice crystals
165c==================================================================
166          DO l=1,nlayer
167            DO ig=1,ngrid
168c             About reffice, do not confuse the mass mean radius
169c             (rayon moyen massique) and the number median radius
170c             (or geometric mean radius, rayon moyen géométrique).
171c             rice is a mass mean radius, whereas rdust
172c             is a geometric mean radius:
173c             number median rad = mass mean rad x exp(-1.5 sigma0^2)
174c             (Montmessin et al. 2004 paragraph 30). Therefore:
175              reffrad(ig,l,iaer)=rice(ig,l)*(1.+nuice_ref)
176              nueffrad(ig,l,iaer)=nuice_ref
177            ENDDO
178          ENDDO
179c==================================================================
180        END SELECT aerkind
181      ENDDO ! iaer (loop on aerosol kind)
182
183      RETURN
184      END
Note: See TracBrowser for help on using the repository browser.