source: trunk/LMDZ.MARS/libf/phymars/updatereffrad_mod.F @ 2511

Last change on this file since 2511 was 2494, checked in by cmathe, 4 years ago

Mars GCM:
co2_ice as scatterer in radiative transfert. Need co2clouds and

activeco2ice .eqv. True. Files involved:

  • aeropacity_mod.F
  • callradite_mod.F
  • physiq_mod.F
  • updatereffrad_mod.F
  • suaer.F90
  • determine co2_ice density from temperature. Used in riceco2 computation.

Files involved:

  • co2cloud.F90
  • improvedco2clouds_mod.F90
  • updaterad.F90
  • updatereffrad_mod.F
  • co2condens_mod4micro.F: variable initialization
  • initracer.F: add nuiceco2_ref = 0.2
  • phyredem.F: remove co2_ice from qsurf since co2_ice => co2ice
  • watercloud_mod.F: tiny typo

CM

File size: 11.5 KB
Line 
1      MODULE updatereffrad_mod
2     
3      IMPLICIT NONE
4     
5      CONTAINS
6     
7      SUBROUTINE updatereffrad(ngrid,nlayer,
8     &                rdust,rstormdust,rtopdust,rice,nuice,
9     &                reffrad,nueffrad, riceco2, nuiceco2,
10     &                pq,tauscaling,tau,pplay, pt)
11       USE updaterad, ONLY: updaterdust, updaterice_micro,
12     &                      updaterice_microco2, updaterice_typ
13       use tracer_mod, only: nqmx, igcm_dust_mass, igcm_dust_number,
14     &                       igcm_h2o_ice, igcm_ccn_mass, radius,
15     &                       igcm_co2_ice, nuiceco2_ref,
16     &                       igcm_ccnco2_number, igcm_ccnco2_mass,
17     &                       igcm_ccn_number, nuice_ref, varian,
18     &                       ref_r0, igcm_dust_submicron,
19     &                       igcm_stormdust_mass,igcm_stormdust_number,
20     &                       igcm_topdust_mass,igcm_topdust_number,
21     &                       rho_ice
22       USE dimradmars_mod, only: nueffdust,naerkind,
23     &            name_iaer,
24     &            iaer_dust_conrath,iaer_dust_doubleq,
25     &            iaer_dust_submicron,iaer_h2o_ice,
26     &            iaer_stormdust_doubleq,iaer_topdust_doubleq
27       use dust_param_mod, only: doubleq, active
28       IMPLICIT NONE
29c=======================================================================
30c   subject:
31c   --------
32c   Subroutine designed to update the aerosol size distribution used by
33c     the radiative transfer scheme. This size distribution is assumed
34c     to be a log-normal distribution, with effective radius "reffrad" and
35c     variance "nueffrad".
36c   At firstcall, "rice" and "nuice" are not known, because
37c     the H2O ice microphysical scheme is called after the radiative
38c     transfer in physiq.F. That's why we assess the size of the
39c     water-ice particles at firstcall (see part 1.2 below).
40c
41c   author:   
42c   ------
43c   J.-B. Madeleine (2009-2010)
44c
45c=======================================================================
46c
47c    Declarations :
48c    -------------
49c
50      include "callkeys.h"
51
52c-----------------------------------------------------------------------
53c     Inputs/outputs:
54c     ------
55
56      INTEGER, INTENT(in) :: ngrid,nlayer
57c     Ice geometric mean radius (m)
58      REAL, INTENT(out) :: rice(ngrid,nlayer)
59c     Estimated effective variance of the size distribution (n.u.)
60      REAL, INTENT(out) :: nuice(ngrid,nlayer)
61c     Tracer mass mixing ratio (kg/kg)
62      REAL, INTENT(in) :: pq(ngrid,nlayer,nqmx)
63      REAL, INTENT(out) :: rdust(ngrid,nlayer) ! Dust geometric mean radius (m)
64      REAL, INTENT(out) :: rstormdust(ngrid,nlayer) ! Dust geometric mean radius (m)   
65      REAL, INTENT(out) :: rtopdust(ngrid,nlayer) ! Dust geometric mean radius (m)
66      REAL, INTENT(in) :: pplay(ngrid,nlayer) ! altitude at the middle of the layers
67      REAL, INTENT(in) :: tau(ngrid,naerkind)
68c     Aerosol effective radius used for radiative transfer (meter)
69      REAL, INTENT(out) :: reffrad(ngrid,nlayer,naerkind)
70c     Aerosol effective variance used for radiative transfer (n.u.)
71      REAL, INTENT(out) :: nueffrad(ngrid,nlayer,naerkind)
72      REAL, INTENT(in) :: tauscaling(ngrid)         ! Convertion factor for qccn and Nccn
73c     CO2 ice mean radius (m)
74      double precision, INTENT(out) :: riceco2(ngrid,nlayer) ! co2 ice radius
75      REAL, INTENT(out) :: nuiceco2(ngrid,nlayer)
76      REAL, INTENT(in) :: pt(ngrid,nlayer) ! temperature
77     
78c     Local variables:
79c     ---------------
80
81      INTEGER :: ig,l          ! 3D grid indices
82      INTEGER :: iaer          ! Aerosol index
83
84c     Number of cloud condensation nuclei near the surface
85c     (only used at firstcall). This value is taken from
86c     Montmessin et al. 2004 JGR 109 E10004 p5 (2E6 part m-3), and
87c     converted to part kg-1 using a typical atmospheric density.
88
89      REAL, PARAMETER :: ccn0 = 1.3E8
90     
91c     For microphysics only:     
92      REAL Mo,No                       ! Mass and number of ccn
93      REAL rhocloud(ngrid,nlayer)  ! Cloud density (kg.m-3)
94c     For CO2 microphysics only:
95      REAL :: rhocloudco2(ngrid, nlayer) ! co2 cloud density
96
97      LOGICAL,SAVE :: firstcall=.true.
98
99      REAL CBRT
100      EXTERNAL CBRT
101
102c==================================================================
103c 1. Update radius from fields from dynamics or initial state
104c==================================================================
105
106c       1.1 Dust particles
107c       ------------------
108        IF (doubleq.AND.active) THEN
109          DO l=1,nlayer
110            DO ig=1, ngrid
111              call updaterdust(pq(ig,l,igcm_dust_mass),
112     &                         pq(ig,l,igcm_dust_number),rdust(ig,l))
113              nueffdust(ig,l) = exp(varian**2.)-1.
114             ENDDO
115           ENDDO
116        ELSE
117          DO l=1,nlayer
118            DO ig=1, ngrid
119              rdust(ig,l) = 0.8E-6
120              nueffdust(ig,l) = 0.3
121            ENDDO
122          ENDDO
123        ENDIF
124
125        ! updating radius of stormdust particles
126        IF (rdstorm.AND.active) THEN
127          DO l=1,nlayer
128            DO ig=1, ngrid
129              call updaterdust(pq(ig,l,igcm_stormdust_mass),
130     &                 pq(ig,l,igcm_stormdust_number),rstormdust(ig,l))
131              nueffdust(ig,l) = exp(varian**2.)-1.
132             ENDDO
133           ENDDO
134        ENDIF
135
136        ! updating radius of topdust particles
137        IF (slpwind.AND.active) THEN
138          DO l=1,nlayer
139            DO ig=1, ngrid
140              call updaterdust(pq(ig,l,igcm_topdust_mass),
141     &                 pq(ig,l,igcm_topdust_number),rtopdust(ig,l))
142              nueffdust(ig,l) = exp(varian**2.)-1.
143             ENDDO
144           ENDDO
145        ENDIF
146       
147c       1.2 Water-ice particles
148c       -----------------------
149
150        IF (water.AND.activice) THEN
151         IF (microphys) THEN
152       
153c    At firstcall, the true number and true mass of cloud condensation nuclei are not known.
154c    Indeed it is scaled on the prescribed dust opacity via a 'tauscaling' coefficient
155c    computed after radiative transfer. If tauscaling is not in startfi, we make an assumption for its value.
156
157          IF (firstcall) THEN
158            !IF (minval(tauscaling).lt.0) tauscaling(:) = 1.e-3 ! default value when non-read in startfi is -1
159            !IF (freedust)                tauscaling(:) = 1.    ! if freedust, enforce no rescaling at all
160            firstcall = .false.
161          ENDIF
162 
163          DO l=1,nlayer
164            DO ig=1,ngrid
165              call updaterice_micro(pq(ig,l,igcm_h2o_ice),
166     &                              pq(ig,l,igcm_ccn_mass),
167     &                              pq(ig,l,igcm_ccn_number),
168     &                              tauscaling(ig),rice(ig,l),
169     &                              rhocloud(ig,l))
170              nuice(ig,l) = nuice_ref
171            ENDDO
172          ENDDO
173         
174        ELSE ! if not microphys
175         
176          DO l=1,nlayer
177            DO ig=1,ngrid   
178              call updaterice_typ(pq(ig,l,igcm_h2o_ice),
179     &                          tau(ig,1),pplay(ig,l),rice(ig,l))
180              nuice(ig,l) = nuice_ref
181            ENDDO
182          ENDDO
183 
184        ENDIF ! of if microphys
185       ENDIF ! of if (water.AND.activice)
186
187
188c       1.3 CO2-ice particles
189
190        IF (co2clouds.AND.activeco2ice) THEN
191          DO l=1,nlayer
192            DO ig=1,ngrid
193              call updaterice_microco2(dble(pq(ig,l,igcm_co2_ice)),
194     &                              dble(pq(ig,l,igcm_ccnco2_mass)),
195     &                              dble(pq(ig,l,igcm_ccnco2_number)),
196     &                              pt(ig,l),
197     &                              tauscaling(ig),riceco2(ig,l),
198     &                              rhocloudco2(ig,l))
199              nuiceco2(ig,l) = nuiceco2_ref
200            END DO
201          ENDDO
202        ENDIF ! of if (co2clouds.AND.activeco2ice)
203
204c==================================================================
205c 2. Radius used in the radiative transfer code (reffrad)
206c==================================================================
207
208      DO iaer = 1, naerkind ! Loop on aerosol kind
209        aerkind: SELECT CASE (name_iaer(iaer))
210c==================================================================
211        CASE("dust_conrath") aerkind         ! Typical dust profile
212c==================================================================
213          DO l=1,nlayer
214            DO ig=1,ngrid
215              reffrad(ig,l,iaer) = rdust(ig,l) *
216     &          (1.e0 + nueffdust(ig,l))**2.5
217              nueffrad(ig,l,iaer) = nueffdust(ig,l)
218            ENDDO
219          ENDDO
220c==================================================================
221        CASE("dust_doubleq") aerkind! Two-moment scheme for dust
222c==================================================================
223          DO l=1,nlayer
224            DO ig=1,ngrid
225              reffrad(ig,l,iaer) = rdust(ig,l) * ref_r0
226              nueffrad(ig,l,iaer) = nueffdust(ig,l)
227            ENDDO
228          ENDDO
229c==================================================================
230        CASE("dust_submicron") aerkind   ! Small dust population
231c==================================================================
232          DO l=1,nlayer
233            DO ig=1,ngrid
234              reffrad(ig,l,iaer)=radius(igcm_dust_submicron)
235              nueffrad(ig,l,iaer)=0.03
236            ENDDO
237          ENDDO     
238c==================================================================
239        CASE("h2o_ice") aerkind             ! Water ice crystals
240c==================================================================
241          DO l=1,nlayer
242            DO ig=1,ngrid
243c             About reffice, do not confuse the mass mean radius
244c             (rayon moyen massique) and the number median radius
245c             (or geometric mean radius, rayon moyen géométrique).
246c             rice is a mass mean radius, whereas rdust
247c             is a geometric mean radius:
248c             number median rad = mass mean rad x exp(-1.5 sigma0^2)
249c             (Montmessin et al. 2004 paragraph 30). Therefore:
250              reffrad(ig,l,iaer)=rice(ig,l)*(1.+nuice_ref)
251              nueffrad(ig,l,iaer)=nuice_ref
252            ENDDO
253          ENDDO
254c==================================================================
255        CASE("co2_ice") aerkind             ! CO2 ice crystals
256c==================================================================
257          DO l=1,nlayer
258            DO ig=1,ngrid
259              reffrad(ig,l,iaer)=real(riceco2(ig,l))*(1.+nuiceco2_ref)
260              nueffrad(ig,l,iaer)=nuiceco2_ref
261            ENDDO
262          ENDDO
263c==================================================================
264        CASE("stormdust_doubleq") aerkind! Two-moment scheme for
265c       stormdust; same distribution than normal dust
266c==================================================================
267          DO l=1,nlayer
268            DO ig=1,ngrid
269              reffrad(ig,l,iaer) = rstormdust(ig,l) * ref_r0
270              nueffrad(ig,l,iaer) = nueffdust(ig,l)
271            ENDDO
272          ENDDO
273c==================================================================
274        CASE("topdust_doubleq") aerkind! MV18: Two-moment scheme for
275c       topdust; same distribution than normal dust
276c==================================================================
277          DO l=1,nlayer
278            DO ig=1,ngrid
279              reffrad(ig,l,iaer) = rtopdust(ig,l) * ref_r0
280              nueffrad(ig,l,iaer) = nueffdust(ig,l)
281            ENDDO
282          ENDDO
283c==================================================================
284        END SELECT aerkind
285      ENDDO ! iaer (loop on aerosol kind)
286
287      END SUBROUTINE updatereffrad
288     
289      END MODULE updatereffrad_mod
Note: See TracBrowser for help on using the repository browser.