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

Last change on this file since 1233 was 1226, checked in by aslmd, 11 years ago

LMDZ.MARS : Replaced comcstfi and planete includes by modules.

File size: 7.7 KB
RevLine 
[38]1      SUBROUTINE updatereffrad(ngrid,nlayer,
2     &                rdust,rice,nuice,
3     &                reffrad,nueffrad,
[744]4     &                pq,tauscaling,tau,pplay)
5       USE updaterad
[1036]6       use tracer_mod, only: nqmx, igcm_dust_mass, igcm_dust_number,
7     &                       igcm_h2o_ice, igcm_ccn_mass, radius,
8     &                       igcm_ccn_number, nuice_ref, varian,
9     &                       ref_r0, igcm_dust_submicron
[1224]10       USE dimradmars_mod, only: nueffdust
[1226]11       USE comcstfi_h
[38]12       IMPLICIT NONE
13c=======================================================================
14c   subject:
15c   --------
16c   Subroutine designed to update the aerosol size distribution used by
17c     the radiative transfer scheme. This size distribution is assumed
18c     to be a log-normal distribution, with effective radius "reffrad" and
19c     variance "nueffrad".
20c   At firstcall, "rice" and "nuice" are not known, because
21c     the H2O ice microphysical scheme is called after the radiative
22c     transfer in physiq.F. That's why we assess the size of the
23c     water-ice particles at firstcall (see part 1.2 below).
24c
25c   author:   
26c   ------
27c   J.-B. Madeleine (2009-2010)
28c
29c=======================================================================
30c
31c    Declarations :
32c    -------------
33c
[1047]34!#include "dimensions.h"
35!#include "dimphys.h"
[38]36#include "callkeys.h"
[1047]37!#include "dimradmars.h"
[1036]38!#include "tracer.h"
[1047]39! naerkind is set in scatterers.h (built when compiling with makegcm -s #)
40#include"scatterers.h"
[38]41#include "aerkind.h"
[1047]42!#include "yomaer.h"
[38]43
44c-----------------------------------------------------------------------
45c     Inputs:
46c     ------
47
48      INTEGER ngrid,nlayer
49c     Ice geometric mean radius (m)
[1047]50      REAL :: rice(ngrid,nlayer)
[38]51c     Estimated effective variance of the size distribution (n.u.)
[1047]52      REAL :: nuice(ngrid,nlayer)
[38]53c     Tracer mass mixing ratio (kg/kg)
54      REAL pq(ngrid,nlayer,nqmx)
[1047]55      REAL rdust(ngrid,nlayer) ! Dust geometric mean radius (m)
[744]56     
57      REAL pplay(ngrid,nlayer) ! altitude at the middle of the layers
58      REAL tau(ngrid,naerkind)
[38]59
[744]60
[38]61c     Outputs:
62c     -------
63
64c     Aerosol effective radius used for radiative transfer (meter)
[1047]65      REAL :: reffrad(ngrid,nlayer,naerkind)
[38]66c     Aerosol effective variance used for radiative transfer (n.u.)
[1047]67      REAL :: nueffrad(ngrid,nlayer,naerkind)
[38]68
69c     Local variables:
70c     ---------------
71
72      INTEGER :: ig,l          ! 3D grid indices
73      INTEGER :: iaer          ! Aerosol index
74
75c     Number of cloud condensation nuclei near the surface
76c     (only used at firstcall). This value is taken from
77c     Montmessin et al. 2004 JGR 109 E10004 p5 (2E6 part m-3), and
78c     converted to part kg-1 using a typical atmospheric density.
79
80      REAL, PARAMETER :: ccn0 = 1.3E8
[629]81     
82c     For microphysics only:     
83      REAL Mo,No                       ! Mass and number of ccn
[1047]84      REAL rhocloud(ngrid,nlayer)  ! Cloud density (kg.m-3)
85      REAL tauscaling(ngrid)         ! Convertion factor for qccn and Nccn
[38]86
[1224]87      LOGICAL,SAVE :: firstcall=.true.
[38]88
89      REAL CBRT
90      EXTERNAL CBRT
91
92c==================================================================
[629]93c 1. Update radius from fields from dynamics or initial state
94c==================================================================
[38]95
[358]96c       1.1 Dust particles
97c       ------------------
98        IF (doubleq.AND.active) THEN
99          DO l=1,nlayer
100            DO ig=1, ngrid
[744]101              call updaterdust(pq(ig,l,igcm_dust_mass),
102     &                         pq(ig,l,igcm_dust_number),rdust(ig,l))
[358]103              nueffdust(ig,l) = exp(varian**2.)-1.
104             ENDDO
105           ENDDO
106        ELSE
107          DO l=1,nlayer
108            DO ig=1, ngrid
109              rdust(ig,l) = 0.8E-6
110              nueffdust(ig,l) = 0.3
111            ENDDO
[38]112          ENDDO
[358]113        ENDIF
[629]114       
[358]115c       1.2 Water-ice particles
116c       -----------------------
[744]117
118        IF (water.AND.activice) THEN
119         IF (microphys) THEN
[1208]120       
121c    At firstcall, the true number and true mass of cloud condensation nuclei are not known.
122c    Indeed it is scaled on the prescribed dust opacity via a 'tauscaling' coefficient
123c    computed after radiative transfer. If tauscaling is not in startfi, we make an assumption for its value.
124
[744]125          IF (firstcall) THEN
[1208]126            IF (minval(tauscaling).lt.0) tauscaling(:) = 1.e-3 ! default value when non-read in startfi is -1
127            IF (freedust)                tauscaling(:) = 1.    ! if freedust, enforce no rescaling at all
128            firstcall = .false.
129          ENDIF
130 
131          DO l=1,nlayer
132            DO ig=1,ngrid
133              call updaterice_micro(pq(ig,l,igcm_h2o_ice),
134     &                              pq(ig,l,igcm_ccn_mass),
135     &                              pq(ig,l,igcm_ccn_number),
136     &                              tauscaling(ig),rice(ig,l),
137     &                              rhocloud(ig,l))
138              nuice(ig,l) = nuice_ref
[358]139            ENDDO
[1208]140          ENDDO
[744]141         
142        ELSE ! if not microphys
143         
144          DO l=1,nlayer
145            DO ig=1,ngrid   
146              call updaterice_typ(pq(ig,l,igcm_h2o_ice),
147     &                          tau(ig,1),pplay(ig,l),rice(ig,l))
148              nuice(ig,l) = nuice_ref
[629]149            ENDDO
[744]150          ENDDO
151 
152        ENDIF ! of if microphys
153       ENDIF ! of if (water.AND.activice)
[38]154
155c==================================================================
156c 2. Radius used in the radiative transfer code (reffrad)
157c==================================================================
158
159      DO iaer = 1, naerkind ! Loop on aerosol kind
160        aerkind: SELECT CASE (name_iaer(iaer))
161c==================================================================
162        CASE("dust_conrath") aerkind         ! Typical dust profile
163c==================================================================
164          DO l=1,nlayer
165            DO ig=1,ngrid
[358]166              reffrad(ig,l,iaer) = rdust(ig,l) *
167     &          (1.e0 + nueffdust(ig,l))**2.5
[38]168              nueffrad(ig,l,iaer) = nueffdust(ig,l)
169            ENDDO
170          ENDDO
171c==================================================================
172        CASE("dust_doubleq") aerkind! Two-moment scheme for dust
173c==================================================================
174          DO l=1,nlayer
175            DO ig=1,ngrid
[358]176              reffrad(ig,l,iaer) = rdust(ig,l) * ref_r0
[38]177              nueffrad(ig,l,iaer) = nueffdust(ig,l)
178            ENDDO
179          ENDDO
180c==================================================================
181        CASE("dust_submicron") aerkind   ! Small dust population
182c==================================================================
183          DO l=1,nlayer
184            DO ig=1,ngrid
185              reffrad(ig,l,iaer)=radius(igcm_dust_submicron)
186              nueffrad(ig,l,iaer)=0.03
187            ENDDO
188          ENDDO     
189c==================================================================
190        CASE("h2o_ice") aerkind             ! Water ice crystals
191c==================================================================
192          DO l=1,nlayer
193            DO ig=1,ngrid
[358]194c             About reffice, do not confuse the mass mean radius
195c             (rayon moyen massique) and the number median radius
196c             (or geometric mean radius, rayon moyen géométrique).
197c             rice is a mass mean radius, whereas rdust
198c             is a geometric mean radius:
199c             number median rad = mass mean rad x exp(-1.5 sigma0^2)
200c             (Montmessin et al. 2004 paragraph 30). Therefore:
[38]201              reffrad(ig,l,iaer)=rice(ig,l)*(1.+nuice_ref)
202              nueffrad(ig,l,iaer)=nuice_ref
203            ENDDO
204          ENDDO
205c==================================================================
206        END SELECT aerkind
207      ENDDO ! iaer (loop on aerosol kind)
208
209      RETURN
210      END
Note: See TracBrowser for help on using the repository browser.