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

Last change on this file since 2091 was 1974, checked in by mvals, 6 years ago

Mars GCM:
Integration of the detached dust layer parametrizations (rocket dust storm, slope wind lifting, CW, and dust injection scheme, DB).
Still experimental, default behaviour (rdstorm=.false., dustinjection=0) identical to previous revision.
NB: Updated newstart requires an updated "surface.nc" containing the "hmons" field.
EM+MV

File size: 8.9 KB
Line 
1      MODULE updatereffrad_mod
2     
3      IMPLICIT NONE
4     
5      CONTAINS
6     
7      SUBROUTINE updatereffrad(ngrid,nlayer,
8     &                rdust,rstormdust,rice,nuice,
9     &                reffrad,nueffrad,
10     &                pq,tauscaling,tau,pplay)
11       USE updaterad, ONLY: updaterdust, updaterice_micro,
12     &                      updaterice_typ
13       use tracer_mod, only: nqmx, igcm_dust_mass, igcm_dust_number,
14     &                       igcm_h2o_ice, igcm_ccn_mass, radius,
15     &                       igcm_ccn_number, nuice_ref, varian,
16     &                       ref_r0, igcm_dust_submicron,
17     &                       igcm_stormdust_mass,igcm_stormdust_number
18       USE dimradmars_mod, only: nueffdust,naerkind,
19     &            name_iaer,
20     &            iaer_dust_conrath,iaer_dust_doubleq,
21     &            iaer_dust_submicron,iaer_h2o_ice,
22     &            iaer_stormdust_doubleq
23
24       IMPLICIT NONE
25c=======================================================================
26c   subject:
27c   --------
28c   Subroutine designed to update the aerosol size distribution used by
29c     the radiative transfer scheme. This size distribution is assumed
30c     to be a log-normal distribution, with effective radius "reffrad" and
31c     variance "nueffrad".
32c   At firstcall, "rice" and "nuice" are not known, because
33c     the H2O ice microphysical scheme is called after the radiative
34c     transfer in physiq.F. That's why we assess the size of the
35c     water-ice particles at firstcall (see part 1.2 below).
36c
37c   author:   
38c   ------
39c   J.-B. Madeleine (2009-2010)
40c
41c=======================================================================
42c
43c    Declarations :
44c    -------------
45c
46      include "callkeys.h"
47
48c-----------------------------------------------------------------------
49c     Inputs/outputs:
50c     ------
51
52      INTEGER, INTENT(in) :: ngrid,nlayer
53c     Ice geometric mean radius (m)
54      REAL, INTENT(out) :: rice(ngrid,nlayer)
55c     Estimated effective variance of the size distribution (n.u.)
56      REAL, INTENT(out) :: nuice(ngrid,nlayer)
57c     Tracer mass mixing ratio (kg/kg)
58      REAL, INTENT(in) :: pq(ngrid,nlayer,nqmx)
59      REAL, INTENT(out) :: rdust(ngrid,nlayer) ! Dust geometric mean radius (m)
60      REAL, INTENT(out) :: rstormdust(ngrid,nlayer) ! Dust geometric mean radius (m)
61      REAL, INTENT(in) :: pplay(ngrid,nlayer) ! altitude at the middle of the layers
62      REAL, INTENT(in) :: tau(ngrid,naerkind)
63c     Aerosol effective radius used for radiative transfer (meter)
64      REAL, INTENT(out) :: reffrad(ngrid,nlayer,naerkind)
65c     Aerosol effective variance used for radiative transfer (n.u.)
66      REAL, INTENT(out) :: nueffrad(ngrid,nlayer,naerkind)
67      REAL, INTENT(in) :: tauscaling(ngrid)         ! Convertion factor for qccn and Nccn
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
81     
82c     For microphysics only:     
83      REAL Mo,No                       ! Mass and number of ccn
84      REAL rhocloud(ngrid,nlayer)  ! Cloud density (kg.m-3)
85
86      LOGICAL,SAVE :: firstcall=.true.
87
88      REAL CBRT
89      EXTERNAL CBRT
90
91c==================================================================
92c 1. Update radius from fields from dynamics or initial state
93c==================================================================
94
95c       1.1 Dust particles
96c       ------------------
97        IF (doubleq.AND.active) THEN
98          DO l=1,nlayer
99            DO ig=1, ngrid
100              call updaterdust(pq(ig,l,igcm_dust_mass),
101     &                         pq(ig,l,igcm_dust_number),rdust(ig,l))
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
114        ! updating radius of stormdust particles
115        IF (rdstorm.AND.active) THEN
116          DO l=1,nlayer
117            DO ig=1, ngrid
118              call updaterdust(pq(ig,l,igcm_stormdust_mass),
119     &                 pq(ig,l,igcm_stormdust_number),rstormdust(ig,l))
120              nueffdust(ig,l) = exp(varian**2.)-1.
121             ENDDO
122           ENDDO
123        ENDIF
124       
125c       1.2 Water-ice particles
126c       -----------------------
127
128        IF (water.AND.activice) THEN
129         IF (microphys) THEN
130       
131c    At firstcall, the true number and true mass of cloud condensation nuclei are not known.
132c    Indeed it is scaled on the prescribed dust opacity via a 'tauscaling' coefficient
133c    computed after radiative transfer. If tauscaling is not in startfi, we make an assumption for its value.
134
135          IF (firstcall) THEN
136            !IF (minval(tauscaling).lt.0) tauscaling(:) = 1.e-3 ! default value when non-read in startfi is -1
137            !IF (freedust)                tauscaling(:) = 1.    ! if freedust, enforce no rescaling at all
138            firstcall = .false.
139          ENDIF
140 
141          DO l=1,nlayer
142            DO ig=1,ngrid
143              call updaterice_micro(pq(ig,l,igcm_h2o_ice),
144     &                              pq(ig,l,igcm_ccn_mass),
145     &                              pq(ig,l,igcm_ccn_number),
146     &                              tauscaling(ig),rice(ig,l),
147     &                              rhocloud(ig,l))
148              nuice(ig,l) = nuice_ref
149            ENDDO
150          ENDDO
151         
152        ELSE ! if not microphys
153         
154          DO l=1,nlayer
155            DO ig=1,ngrid   
156              call updaterice_typ(pq(ig,l,igcm_h2o_ice),
157     &                          tau(ig,1),pplay(ig,l),rice(ig,l))
158              nuice(ig,l) = nuice_ref
159            ENDDO
160          ENDDO
161 
162        ENDIF ! of if microphys
163       ENDIF ! of if (water.AND.activice)
164
165c==================================================================
166c 2. Radius used in the radiative transfer code (reffrad)
167c==================================================================
168
169      DO iaer = 1, naerkind ! Loop on aerosol kind
170        aerkind: SELECT CASE (name_iaer(iaer))
171c==================================================================
172        CASE("dust_conrath") aerkind         ! Typical dust profile
173c==================================================================
174          DO l=1,nlayer
175            DO ig=1,ngrid
176              reffrad(ig,l,iaer) = rdust(ig,l) *
177     &          (1.e0 + nueffdust(ig,l))**2.5
178              nueffrad(ig,l,iaer) = nueffdust(ig,l)
179            ENDDO
180          ENDDO
181c==================================================================
182        CASE("dust_doubleq") aerkind! Two-moment scheme for dust
183c==================================================================
184          DO l=1,nlayer
185            DO ig=1,ngrid
186              reffrad(ig,l,iaer) = rdust(ig,l) * ref_r0
187              nueffrad(ig,l,iaer) = nueffdust(ig,l)
188            ENDDO
189          ENDDO
190c==================================================================
191        CASE("dust_submicron") aerkind   ! Small dust population
192c==================================================================
193          DO l=1,nlayer
194            DO ig=1,ngrid
195              reffrad(ig,l,iaer)=radius(igcm_dust_submicron)
196              nueffrad(ig,l,iaer)=0.03
197            ENDDO
198          ENDDO     
199c==================================================================
200        CASE("h2o_ice") aerkind             ! Water ice crystals
201c==================================================================
202          DO l=1,nlayer
203            DO ig=1,ngrid
204c             About reffice, do not confuse the mass mean radius
205c             (rayon moyen massique) and the number median radius
206c             (or geometric mean radius, rayon moyen géométrique).
207c             rice is a mass mean radius, whereas rdust
208c             is a geometric mean radius:
209c             number median rad = mass mean rad x exp(-1.5 sigma0^2)
210c             (Montmessin et al. 2004 paragraph 30). Therefore:
211              reffrad(ig,l,iaer)=rice(ig,l)*(1.+nuice_ref)
212              nueffrad(ig,l,iaer)=nuice_ref
213            ENDDO
214          ENDDO
215c==================================================================
216        CASE("stormdust_doubleq") aerkind! Two-moment scheme for
217c       stormdust; same distribution than normal dust
218c==================================================================
219          DO l=1,nlayer
220            DO ig=1,ngrid
221              reffrad(ig,l,iaer) = rstormdust(ig,l) * ref_r0
222              nueffrad(ig,l,iaer) = nueffdust(ig,l)
223            ENDDO
224          ENDDO
225c==================================================================
226        END SELECT aerkind
227      ENDDO ! iaer (loop on aerosol kind)
228
229      END SUBROUTINE updatereffrad
230     
231      END MODULE updatereffrad_mod
Note: See TracBrowser for help on using the repository browser.