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

Last change on this file since 1944 was 1266, checked in by aslmd, 11 years ago

LMDZ.MARS
IMPORTANT CHANGE

  • Remove all reference/use of nlayermx and dimphys.h
  • Made use of automatic arrays whenever arrays are needed with dimension nlayer
  • Remove lots of obsolete reference to dimensions.h
  • Converted iono.h and param_v4.h into corresponding modules

(with embedded subroutine to allocate arrays)
(no arrays allocated if thermosphere not used)

  • Deleted param.h and put contents into module param_v4_h
  • Adapted testphys1d, newstart, etc...
  • Made DATA arrays in param_read to be initialized by subroutine

fill_data_thermos in module param_v4_h

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