source: trunk/LMDZ.MARS/libf/phymars/aeropacity.F @ 246

Last change on this file since 246 was 222, checked in by aslmd, 13 years ago

MESSAGE DE JB MADELEINE

C'était juste pour vous dire que j'ai fait un peu de rangement dans le
DATAFILE concernant les propriétés de la poussière (directement dans le
répertoire /u/forget/WWW/datagcm/datafile/), car lorsque Ockert-Bell
dans le domaine solaire était utilisé avec Forget 1998 dans l'IR, le
rapport Solaire/IR "solsir" n'était pas rigoureusement égal à 2.

Du coup il faut changer les noms des fichiers dans suaer.F90

REMARQUE: Le rapport "solsir" est sorti dans les logs au firstcall, et
vous verrez qu'il n'est pas égal à 2 lorsque ces propriétés sont
utilisées. C'EST NORMAL! En effet, j'ai réglé la longueur d'onde de
référence de la poussière dans l'IR à 9.3um pour pouvoir comparer
l'opacité donnée en output avec TES. Or le fameux solsir=2 utilisé
partout date de l'époque où la longueur de référence était celle du
canal "T9" d'IRTM qui est 9um et non 9.3um!

En résumé, au firstcall, le GCM affiche Qext(0.67um)/Qext(9.3um), et non
l'ancien solsir qui lui vaut Qext(0.67um)/Qext(9um), d'où un résultat
qui n'est pas égal à deux. Mais rassurez-vous, Qext(0.67um)/Qext(9um)
dans les fichiers d'input vaut bien 2.

Également, j'ai un peu modifié aeropacity.F car il affichait le
"ccn_factor" à tout va dans les logs. Il est également attaché à ce mail.

File size: 20.2 KB
Line 
1      SUBROUTINE aeropacity(ngrid,nlayer,nq,zday,pplay,pplev,ls,
2     &    pq,ccn,tauref,tau,aerosol,reffrad,nueffrad,
3     &    QREFvis3d,QREFir3d,omegaREFvis3d,omegaREFir3d)
4                                                   
5! to use  'getin'
6      USE ioipsl_getincom
7       IMPLICIT NONE
8c=======================================================================
9c   subject:
10c   --------
11c   Computing aerosol optical depth in each gridbox.
12c
13c   author: F.Forget
14c   ------
15c   update F. Montmessin (water ice scheme)
16c      and S. Lebonnois (12/06/2003) compatibility dust/ice/chemistry
17c   update J.-B. Madeleine 2008-2009:
18c       - added 3D scattering by aerosols;
19c       - dustopacity transferred from physiq.F to callradite.F,
20c           and renamed into aeropacity.F;
21c   
22c   input:
23c   -----
24c   ngrid             Number of gridpoint of horizontal grid
25c   nlayer            Number of layer
26c   nq                Number of tracer
27c   zday                  Date (time since Ls=0, in martian days)
28c   ls                Solar longitude (Ls) , radian
29c   pplay,pplev       pressure (Pa) in the middle and boundary of each layer
30c   pq                Dust mixing ratio (used if tracer =T and active=T).
31c   reffrad(ngrid,nlayer,naerkind)  Aerosol effective radius
32c   QREFvis3d(ngridmx,nlayermx,naerkind) \ 3d extinction coefficients
33c   QREFir3d(ngridmx,nlayermx,naerkind)  / at reference wavelengths;
34c   omegaREFvis3d(ngridmx,nlayermx,naerkind) \ 3d single scat. albedo
35c   omegaREFir3d(ngridmx,nlayermx,naerkind)  / at reference wavelengths;
36c
37c   output:
38c   -------
39c   tauref       Prescribed mean column optical depth at 700 Pa
40c   tau          Column total visible dust optical depth at each point
41c   aerosol      aerosol(ig,l,1) is the dust optical
42c                depth in layer l, grid point ig
43
44c
45c=======================================================================
46#include "dimensions.h"
47#include "dimphys.h"
48#include "callkeys.h"
49#include "comcstfi.h"
50#include "comgeomfi.h"
51#include "dimradmars.h"
52#include "yomaer.h"
53#include "tracer.h"
54#include "planete.h"
55#include "aerkind.h"
56
57c-----------------------------------------------------------------------
58c
59c    Declarations :
60c    --------------
61c
62c    Input/Output
63c    ------------
64      INTEGER ngrid,nlayer,nq
65
66      REAL ls,zday,expfactor   
67      REAL pplev(ngrid,nlayer+1),pplay(ngrid,nlayer)
68      REAL pq(ngrid,nlayer,nq)
69      REAL tauref(ngrid), tau(ngrid,naerkind)
70      REAL aerosol(ngrid,nlayer,naerkind)
71      REAL dsodust(ngridmx,nlayermx)
72      REAL reffrad(ngrid,nlayer,naerkind)
73      REAL nueffrad(ngrid,nlayer,naerkind)
74      REAL QREFvis3d(ngridmx,nlayermx,naerkind)
75      REAL QREFir3d(ngridmx,nlayermx,naerkind)
76      REAL omegaREFvis3d(ngridmx,nlayermx,naerkind)
77      REAL omegaREFir3d(ngridmx,nlayermx,naerkind)
78c
79c    Local variables :
80c    -----------------
81      INTEGER l,ig,iq,i,j
82      INTEGER iaer           ! Aerosol index
83      real topdust(ngridmx)
84      real zlsconst, zp
85      real taueq,tauS,tauN
86c     Mean Qext(vis)/Qext(ir) profile
87      real msolsir(nlayermx,naerkind)
88c     Mean Qext(ir)/Qabs(ir) profile
89      real mqextsqabs(nlayermx,naerkind)
90c     Variables used when multiple particle sizes are used
91c       for dust or water ice particles in the radiative transfer
92c       (see callradite.F for more information).
93      REAL taudusttmp(ngridmx)! Temporary dust opacity
94                               !   used before scaling
95      REAL taudustvis(ngridmx) ! Dust opacity after scaling
96      REAL taudusttes(ngridmx) ! Dust opacity at IR ref. wav. as
97                               !   "seen" by the GCM.
98      REAL taucloudvis(ngridmx)! Cloud opacity at visible
99                               !   reference wavelength
100      REAL taucloudtes(ngridmx)! Cloud opacity at infrared
101                               !   reference wavelength using
102                               !   Qabs instead of Qext
103                               !   (direct comparison with TES)
104      REAL qdust(ngridmx,nlayermx) ! True dust mass mixing ratio
105      REAL ccn(ngridmx,nlayermx)   ! Cloud condensation nuclei
106                                   !   (particules kg-1)
107      REAL qtot(ngridmx)           ! Dust column (kg m-2)
108
109c     CCN reduction factor
110      REAL, PARAMETER :: ccn_factor = 4.5  !! comme TESTS_JB // 1. avant
111
112c
113c   local saved variables
114c   ---------------------
115
116      REAL topdust0(ngridmx)
117      SAVE topdust0
118c     Level under which the dust mixing ratio is held constant
119c       when computing the dust opacity in each layer
120c       (this applies when doubleq and active are true)
121      INTEGER, PARAMETER :: cstdustlevel = 7
122
123      LOGICAL firstcall
124      DATA firstcall/.true./
125      SAVE firstcall
126
127! indexes of water ice and dust tracers:
128      INTEGER,SAVE :: nqdust(nqmx) ! to store the indexes of dust tracers
129      INTEGER,SAVE :: i_ice=0  ! water ice
130      CHARACTER(LEN=20) :: txt ! to temporarly store text
131      CHARACTER(LEN=1) :: txt2 ! to temporarly store text
132! indexes of dust scatterers:
133      INTEGER,SAVE :: iaerdust(naerkind)
134      INTEGER,SAVE :: naerdust ! number of dust scatterers
135
136      tau(1:ngrid,1:naerkind)=0
137
138! identify tracers
139
140      IF (firstcall) THEN
141        ! identify scatterers that are dust
142        naerdust=0
143        DO iaer=1,naerkind
144          txt=name_iaer(iaer)
145          IF (txt(1:4).eq."dust") THEN
146            naerdust=naerdust+1
147            iaerdust(naerdust)=iaer
148          ENDIF
149        ENDDO
150        ! identify tracers which are dust
151        i=0
152        DO iq=1,nq
153          txt=noms(iq)
154          IF (txt(1:4).eq."dust") THEN
155          i=i+1
156          nqdust(i)=iq
157          ENDIF
158        ENDDO
159
160        IF (water.AND.activice) THEN
161          i_ice=igcm_h2o_ice
162          write(*,*) "aeropacity: i_ice=",i_ice
163        ENDIF
164
165c       altitude of the top of the aerosol layer (km) at Ls=2.76rad:
166c       in the Viking year scenario
167        DO ig=1,ngrid
168            topdust0(ig)=60. -22.*SIN(lati(ig))**2
169        END DO
170
171c       typical profile of solsir and (1-w)^(-1):
172        msolsir(1:nlayer,1:naerkind)=0
173        mqextsqabs(1:nlayer,1:naerkind)=0
174        WRITE(*,*) "Typical profiles of Qext(vis)/Qext(IR)"
175        WRITE(*,*) "  and Qext(IR)/Qabs(IR):"
176        DO iaer = 1, naerkind ! Loop on aerosol kind
177          WRITE(*,*) "Aerosol # ",iaer
178          DO l=1,nlayer
179            DO ig=1,ngridmx
180              msolsir(l,iaer)=msolsir(l,iaer)+
181     &              QREFvis3d(ig,l,iaer)/
182     &              QREFir3d(ig,l,iaer)
183              mqextsqabs(l,iaer)=mqextsqabs(l,iaer)+
184     &              (1.E0-omegaREFir3d(ig,l,iaer))**(-1)
185            ENDDO
186            msolsir(l,iaer)=msolsir(l,iaer)/REAL(ngridmx)
187            mqextsqabs(l,iaer)=mqextsqabs(l,iaer)/REAL(ngridmx)
188          ENDDO
189          WRITE(*,*) "solsir: ",msolsir(:,iaer)
190          WRITE(*,*) "Qext/Qabs(IR): ",mqextsqabs(:,iaer)
191        ENDDO
192
193!       load value of tauvis from callphys.def (if given there,
194!       otherwise default value read from starfi.nc file will be used)
195        call getin("tauvis",tauvis)
196
197!       Some information about the water cycle
198        IF (water) THEN
199          write(*,*) "water_param CCN reduc. fac. ", ccn_factor
200        ENDIF
201
202        firstcall=.false.
203
204      END IF
205
206c     Vertical column optical depth at 700.Pa
207c     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
208      IF(iaervar.eq.1) THEN
209         do ig=1, ngridmx
210          tauref(ig)=max(tauvis,1.e-9) ! tauvis=cste (set in callphys.def
211                                       ! or read in starfi
212        end do
213      ELSE IF (iaervar.eq.2) THEN   ! << "Viking" Scenario>>
214
215        tauref(1) = 0.7+.3*cos(ls+80.*pi/180.) ! like seen by VL1
216        do ig=2,ngrid
217          tauref(ig) = tauref(1)
218        end do
219
220      ELSE IF (iaervar.eq.3) THEN  ! << "MGS" scenario >>
221
222        taueq= 0.2 +(0.5-0.2) *(cos(0.5*(ls-4.363)))**14
223        tauS= 0.1 +(0.5-0.1)  *(cos(0.5*(ls-4.363)))**14
224        tauN = 0.1
225c          if (peri_day.eq.150) then
226c            tauS=0.1
227c            tauN=0.1 +(0.5-0.1)  *(cos(0.5*(ls+pi-4.363)))**14
228c            taueq= 0.2 +(0.5-0.2) *(cos(0.5*(ls+pi-4.363)))**14
229c           endif
230        do ig=1,ngrid/2  ! Northern hemisphere
231          tauref(ig)= tauN +
232     &    (taueq-tauN)*0.5*(1+tanh((45-lati(ig)*180./pi)*6/60))
233        end do
234        do ig=ngrid/2+1, ngridmx  ! Southern hemisphere
235          tauref(ig)= tauS +
236     &    (taueq-tauS)*0.5*(1+tanh((45+lati(ig)*180./pi)*6/60))
237        end do
238      ELSE IF ((iaervar.eq.4).or.
239     &        ((iaervar.ge.24).and.(iaervar.le.26)))
240     &     THEN  ! << "TES assimilated dust scenarios >>
241        call readtesassim(ngrid,nlayer,zday,pplev,tauref)
242
243      ELSE IF (iaervar.eq.5) THEN   ! << Escalier Scenario>>
244c         tauref(1) = 0.2
245c         if ((ls.ge.210.*pi/180.).and.(ls.le.330.*pi/180.))
246c    &                              tauref(1) = 2.5
247        tauref(1) = 2.5
248        if ((ls.ge.30.*pi/180.).and.(ls.le.150.*pi/180.))
249     &                              tauref(1) = .2
250
251        do ig=2,ngrid
252          tauref(ig) = tauref(1)
253        end do
254      ELSE
255        stop 'problem with iaervar in aeropacity.F'
256      ENDIF
257
258c -----------------------------------------------------------------
259c Computing the opacity in each layer
260c -----------------------------------------------------------------
261
262      DO iaer = 1, naerkind ! Loop on aerosol kind
263c     --------------------------------------------
264        aerkind: SELECT CASE (name_iaer(iaer))
265c==================================================================
266        CASE("dust_conrath") aerkind      ! Typical dust profile
267c==================================================================
268
269c       Altitude of the top of the dust layer
270c       ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
271        zlsconst=SIN(ls-2.76)
272        if (iddist.eq.1) then
273          do ig=1,ngrid
274             topdust(ig)=topdustref         ! constant dust layer top
275          end do
276
277        else if (iddist.eq.2) then          ! "Viking" scenario
278          do ig=1,ngrid
279            topdust(ig)=topdust0(ig)+18.*zlsconst
280          end do
281
282        else if(iddist.eq.3) then         !"MGS" scenario
283          do ig=1,ngrid
284            topdust(ig)=60.+18.*zlsconst
285     &                -(32+18*zlsconst)*sin(lati(ig))**4
286     &                 - 8*zlsconst*(sin(lati(ig)))**5
287          end do
288        endif
289
290c       Optical depth in each layer :
291c       ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
292        if(iddist.ge.1) then
293
294          expfactor=0.
295          DO l=1,nlayer
296            DO ig=1,ngrid
297c             Typical mixing ratio profile
298              if(pplay(ig,l).gt.700.
299     $                        /(988.**(topdust(ig)/70.))) then
300                zp=(700./pplay(ig,l))**(70./topdust(ig))
301                 expfactor=max(exp(0.007*(1.-max(zp,1.))),1.e-3)
302              else   
303                expfactor=1.e-3
304              endif
305c             Vertical scaling function
306              aerosol(ig,l,iaer)= (pplev(ig,l)-pplev(ig,l+1)) *
307     &          expfactor *
308     &          QREFvis3d(ig,l,iaer) / QREFvis3d(ig,1,iaer)
309            ENDDO
310          ENDDO
311
312        else if(iddist.eq.0) then   
313c         old dust vertical distribution function (pollack90)
314          DO l=1,nlayer
315             DO ig=1,ngrid
316                zp=700./pplay(ig,l)
317                aerosol(ig,l,1)= tauref(ig)/700. *
318     s           (pplev(ig,l)-pplev(ig,l+1))
319     s           *max( exp(.03*(1.-max(zp,1.))) , 1.E-3 )
320             ENDDO
321          ENDDO
322        end if
323
324c==================================================================
325        CASE("dust_doubleq") aerkind! Two-moment scheme for dust
326c        (transport of mass and number mixing ratio)
327c==================================================================
328
329          DO l=1,nlayer
330            IF (l.LE.cstdustlevel) THEN
331c           Opacity in the first levels is held constant to
332c             avoid unrealistic values due to constant lifting:
333              DO ig=1,ngrid
334                aerosol(ig,l,iaer) =
335     &          (  0.75 * QREFvis3d(ig,cstdustlevel,iaer) /
336     &          ( rho_dust * reffrad(ig,cstdustlevel,iaer) )  ) *
337     &          pq(ig,cstdustlevel,igcm_dust_mass) *
338     &          ( pplev(ig,l) - pplev(ig,l+1) ) / g
339              ENDDO
340            ELSE
341              DO ig=1,ngrid
342                aerosol(ig,l,iaer) =
343     &          (  0.75 * QREFvis3d(ig,l,iaer) /
344     &          ( rho_dust * reffrad(ig,l,iaer) )  ) *
345     &          pq(ig,l,igcm_dust_mass) *
346     &          ( pplev(ig,l) - pplev(ig,l+1) ) / g
347              ENDDO
348            ENDIF
349          ENDDO
350
351c==================================================================
352        CASE("dust_submicron") aerkind   ! Small dust population
353c==================================================================
354
355          DO l=1,nlayer
356            IF (l.LE.cstdustlevel) THEN
357c           Opacity in the first levels is held constant to
358c             avoid unrealistic values due to constant lifting:
359              DO ig=1,ngrid
360                aerosol(ig,l,iaer) =
361     &          (  0.75 * QREFvis3d(ig,cstdustlevel,iaer) /
362     &          ( rho_dust * reffrad(ig,cstdustlevel,iaer) )  ) *
363     &          pq(ig,cstdustlevel,igcm_dust_submicron) *
364     &          ( pplev(ig,l) - pplev(ig,l+1) ) / g
365              ENDDO
366            ELSE
367              DO ig=1,ngrid
368                aerosol(ig,l,iaer) =
369     &          (  0.75 * QREFvis3d(ig,l,iaer) /
370     &          ( rho_dust * reffrad(ig,l,iaer) )  ) *
371     &          pq(ig,l,igcm_dust_submicron) *
372     &          ( pplev(ig,l) - pplev(ig,l+1) ) / g
373              ENDDO
374            ENDIF
375          ENDDO
376
377c==================================================================
378        CASE("h2o_ice") aerkind             ! Water ice crystals
379c==================================================================
380
381c       1. Initialization
382        aerosol(1:ngrid,1:nlayer,iaer) = 0.
383        taucloudvis(1:ngrid) = 0.
384        taucloudtes(1:ngrid) = 0.
385c       2. Opacity calculation
386        DO ig=1, ngrid
387          DO l=1,nlayer
388            aerosol(ig,l,iaer) = max(1E-20,
389     &        (  0.75 * QREFvis3d(ig,l,iaer) /
390     &        ( rho_ice * reffrad(ig,l,iaer) )  ) *
391     &        pq(ig,l,i_ice) *
392     &        ( pplev(ig,l) - pplev(ig,l+1) ) / g
393     &                              )
394            taucloudvis(ig) = taucloudvis(ig) + aerosol(ig,l,iaer)
395            taucloudtes(ig) = taucloudtes(ig) + aerosol(ig,l,iaer)*
396     &        QREFir3d(ig,l,iaer) / QREFvis3d(ig,l,iaer) *
397     &        ( 1.E0 - omegaREFir3d(ig,l,iaer) )
398          ENDDO
399        ENDDO
400c       3. Outputs
401        IF (ngrid.NE.1) THEN
402          CALL WRITEDIAGFI(ngridmx,'tauVIS','tauext VIS refwvl',
403     &      ' ',2,taucloudvis)
404          CALL WRITEDIAGFI(ngridmx,'tauTES','tauabs IR refwvl',
405     &      ' ',2,taucloudtes)
406          IF (callstats) THEN
407            CALL wstats(ngridmx,'tauVIS','tauext VIS refwvl',
408     &        ' ',2,taucloudvis)
409            CALL wstats(ngridmx,'tauTES','tauabs IR refwvl',
410     &        ' ',2,taucloudtes)
411          ENDIF
412        ELSE
413c         CALL writeg1d(ngrid,1,taucloudtes,'tautes','NU')
414        ENDIF
415c==================================================================
416        END SELECT aerkind
417c     -----------------------------------
418      ENDDO ! iaer (loop on aerosol kind)
419
420c -----------------------------------------------------------------
421c Rescaling each layer to reproduce the choosen (or assimilated)
422c   dust extinction opacity at visible reference wavelength, which
423c   is originally scaled to an equivalent 700Pa pressure surface.
424c -----------------------------------------------------------------
425
426      taudusttmp(1:ngrid)=0.
427      DO iaer=1,naerdust
428        DO l=1,nlayer
429          DO ig=1,ngrid
430c           Scaling factor
431            taudusttmp(ig) = taudusttmp(ig) +
432     &                       aerosol(ig,l,iaerdust(iaer))
433          ENDDO
434        ENDDO
435      ENDDO
436      DO iaer=1,naerdust
437        DO l=1,nlayer
438          DO ig=1,ngrid
439            aerosol(ig,l,iaerdust(iaer)) = max(1E-20,
440     &                   tauref(ig) *
441     &                   pplev(ig,1) / 700.E0 *
442     &                   aerosol(ig,l,iaerdust(iaer)) /
443     &                   taudusttmp(ig)
444     &                                        )
445          ENDDO
446        ENDDO
447      ENDDO
448
449c -----------------------------------------------------------------
450c Computing the number of condensation nuclei
451c -----------------------------------------------------------------
452      DO iaer = 1, naerkind ! Loop on aerosol kind
453c     --------------------------------------------
454        aerkind2: SELECT CASE (name_iaer(iaer))
455c==================================================================
456        CASE("dust_conrath") aerkind2     ! Typical dust profile
457c==================================================================
458          DO l=1,nlayer
459            DO ig=1,ngrid
460              ccn(ig,l) = max(aerosol(ig,l,iaer) /
461     &                  pi / QREFvis3d(ig,l,iaer) *
462     &                  (1.+nueffrad(ig,l,iaer))**3. /
463     &                  reffrad(ig,l,iaer)**2. * g /
464     &                  (pplev(ig,l)-pplev(ig,l+1)),1e-30)
465            ENDDO
466          ENDDO
467c==================================================================
468        CASE("dust_doubleq") aerkind2!Two-moment scheme for dust
469c        (transport of mass and number mixing ratio)
470c==================================================================
471          qtot(1:ngridmx) = 0.
472          DO l=1,nlayer
473            DO ig=1,ngrid
474              qdust(ig,l) = pq(ig,l,igcm_dust_mass) * tauref(ig) *
475     &                      pplev(ig,1) / 700.E0 / taudusttmp(ig)
476              qtot(ig) = qtot(ig) + qdust(ig,l) *
477     &                   (pplev(ig,l)-pplev(ig,l+1)) / g
478              ccn(ig,l) = max( ( ref_r0 /
479     &                    reffrad(ig,l,iaer) )**3. *
480     &                    r3n_q * qdust(ig,l) ,1e-30)
481            ENDDO
482          ENDDO
483c==================================================================
484        END SELECT aerkind2
485c     -----------------------------------
486      ENDDO ! iaer (loop on aerosol kind)
487
488
489c -----------------------------------------------------------------
490c -----------------------------------------------------------------
491c  Reduce number of nuclei
492!         TEMPORAIRE : r�duction du nombre de nuclei FF 04/200
493!         reduction facteur 3
494!         ccn(ig,l) = ccn(ig,l) / 27.
495!         reduction facteur 2
496!         ccn(ig,l) = ccn(ig,l) / 8.
497c -----------------------------------------------------------------
498       DO l=1,nlayer
499         DO ig=1,ngrid
500            ccn(ig,l) = ccn(ig,l) / ccn_factor
501         ENDDO
502       ENDDO
503c -----------------------------------------------------------------
504c -----------------------------------------------------------------
505
506
507c -----------------------------------------------------------------
508c Column integrated visible optical depth in each point
509c -----------------------------------------------------------------
510      DO iaer=1,naerkind
511        do l=1,nlayer
512           do ig=1,ngrid
513             tau(ig,iaer) = tau(ig,iaer) + aerosol(ig,l,iaer)
514           end do
515        end do
516      ENDDO
517c -----------------------------------------------------------------
518c Density scaled opacity and column opacity output
519c -----------------------------------------------------------------
520      dsodust(1:ngrid,1:nlayer) = 0.
521      DO iaer=1,naerdust
522        DO l=1,nlayermx
523          DO ig=1,ngrid
524            dsodust(ig,l) = dsodust(ig,l) +
525     &                      aerosol(ig,l,iaerdust(iaer)) * g /
526     &                      (pplev(ig,l) - pplev(ig,l+1))
527          ENDDO
528        ENDDO
529        IF (ngrid.NE.1) THEN
530          write(txt2,'(i1.1)') iaer
531          call WRITEDIAGFI(ngridmx,'taudust'//txt2,
532     &                    'Dust col opacity',
533     &                    ' ',2,tau(1,iaerdust(iaer)))
534          IF (callstats) THEN
535            CALL wstats(ngridmx,'taudust'//txt2,
536     &                 'Dust col opacity',
537     &                 ' ',2,tau(1,iaerdust(iaer)))
538          ENDIF
539        ENDIF
540      ENDDO
541
542      IF (ngrid.NE.1) THEN
543c       CALL WRITEDIAGFI(ngridmx,'dsodust','tau*g/dp',
544c    &                    'm2.kg-1',3,dsodust)
545        IF (callstats) THEN
546          CALL wstats(ngridmx,'dsodust',
547     &               'tau*g/dp',
548     &               'm2.kg-1',3,dsodust)
549        ENDIF
550c       CALL WRITEDIAGFI(ngridmx,'ccn','Cond. nuclei',
551c    &                    'part kg-1',3,ccn)
552      ELSE
553        CALL writeg1d(ngrid,nlayer,dsodust,'dsodust','m2.kg-1')
554      ENDIF
555c -----------------------------------------------------------------
556      return
557      end
Note: See TracBrowser for help on using the repository browser.