source: trunk/LMDZ.MARS/libf/phymars/callsedim_mod.F @ 2316

Last change on this file since 2316 was 2312, checked in by lrossi, 6 years ago

MARS GCM:
Implementation of HDO in the physics
New tracers hdo_vap and hdo_ice are added. Cf. traceur.def.isotopes in deftank for exemple of traceur.def.
All HDO related computations are activated by flag hdo=.true. in callphys.def. (see callphys.def.hdo in deftank for an example)
Additional option hdofrac (true by default) allows for turning on/off fractionation (for tests).
For now, only functional with simplified cloud scheme (so microphys=.false. and activice=.false. also recommended).
Initialisation of start files can be done with option 'inihdo' in newstart.
LR

File size: 22.2 KB
Line 
1      MODULE callsedim_mod
2
3      IMPLICIT NONE
4
5      CONTAINS
6
7      SUBROUTINE callsedim(ngrid,nlay,ptimestep,
8     &                pplev,zlev,zlay,pt,pdt,
9     &                rdust,rstormdust,rtopdust,
10     &                rice,rsedcloud,rhocloud,
11     &                pq,pdqfi,pdqsed,pdqs_sed,nq,
12     &                tau,tauscaling)
13
14      USE ioipsl_getin_p_mod, only: getin_p
15      USE updaterad, only: updaterdust,updaterice_micro,updaterice_typ
16      USE tracer_mod, only: noms, igcm_dust_mass, igcm_dust_number,
17     &                      rho_dust, rho_q, radius, varian,
18     &                      igcm_ccn_mass, igcm_ccn_number,
19     &                      igcm_h2o_ice, igcm_hdo_ice,
20     &                      nuice_sed, nuice_ref,
21     &                      igcm_ccnco2_mass,igcm_ccnco2_number,
22     &                      igcm_co2_ice, igcm_stormdust_mass,
23     &                      igcm_stormdust_number,igcm_topdust_mass,
24     &                      igcm_topdust_number
25      USE newsedim_mod, ONLY: newsedim
26      USE comcstfi_h, ONLY: g
27      USE dimradmars_mod, only: naerkind
28      IMPLICIT NONE
29
30c=======================================================================
31c      Sedimentation of the  Martian aerosols
32c      depending on their density and radius
33c
34c      F.Forget 1999
35c
36c      Modified by J.-B. Madeleine 2010: Now includes the doubleq
37c        technique in order to have only one call to callsedim in
38c        physiq.F.
39c
40c      Modified by J. Audouard 09/16: Now includes the co2clouds case
41c        If the co2 microphysics is on, then co2 theice & ccn tracers
42c        are being sedimented in the microtimestep (co2cloud.F), not
43c        in this routine.
44c
45c=======================================================================
46
47c-----------------------------------------------------------------------
48c   declarations:
49c   -------------
50     
51      include "callkeys.h"
52
53c
54c   arguments:
55c   ----------
56
57      integer,intent(in) :: ngrid  ! number of horizontal grid points
58      integer,intent(in) :: nlay   ! number of atmospheric layers
59      real,intent(in) :: ptimestep ! physics time step (s)
60      real,intent(in) :: pplev(ngrid,nlay+1) ! pressure at inter-layers (Pa)
61      real,intent(in) :: zlev(ngrid,nlay+1) ! altitude at layer boundaries
62      real,intent(in) :: zlay(ngrid,nlay)   ! altitude at the middle of the layers
63      real,intent(in) :: pt(ngrid,nlay) ! temperature at mid-layer (K)
64      real,intent(in) :: pdt(ngrid,nlay) ! tendency on temperature, from
65                                         ! previous processes (K/s)
66c    Aerosol radius provided by the water ice microphysical scheme:
67      real,intent(out) :: rdust(ngrid,nlay) ! Dust geometric mean radius (m)
68      real,intent(out) :: rstormdust(ngrid,nlay) ! Stormdust geometric mean radius (m)
69      real,intent(out) :: rtopdust(ngrid,nlay) ! topdust geometric mean radius (m)
70      real,intent(out) :: rice(ngrid,nlay)  ! H2O Ice geometric mean radius (m)
71c     Sedimentation radius of water ice
72      real,intent(in) :: rsedcloud(ngrid,nlay)
73c     Cloud density (kg.m-3)
74      real,intent(inout) :: rhocloud(ngrid,nlay)
75c    Traceurs :
76      real,intent(in) :: pq(ngrid,nlay,nq)  ! tracers (kg/kg)
77      real,intent(in) :: pdqfi(ngrid,nlay,nq)  ! tendency before sedimentation (kg/kg.s-1)
78      real,intent(out) :: pdqsed(ngrid,nlay,nq) ! tendency due to sedimentation (kg/kg.s-1)
79      real,intent(out) :: pdqs_sed(ngrid,nq)    ! flux at surface (kg.m-2.s-1)
80      integer,intent(in) :: nq  ! number of tracers
81      real,intent(in) :: tau(ngrid,naerkind) ! dust opacity
82      real,intent(in) :: tauscaling(ngrid)
83     
84c   local:
85c   ------
86
87      INTEGER l,ig, iq
88
89      real zqi(ngrid,nlay,nq) ! to locally store tracers
90      real zt(ngrid,nlay) ! to locally store temperature
91      real masse (ngrid,nlay) ! Layer mass (kg.m-2)
92      real epaisseur (ngrid,nlay) ! Layer thickness (m)
93      real wq(ngrid,nlay+1) ! displaced tracer mass (kg.m-2)
94      real r0(ngrid,nlay) ! geometric mean radius used for
95                                !   sedimentation (m)
96      real r0dust(ngrid,nlay) ! geometric mean radius used for
97                                    !   dust (m)
98      real r0stormdust(ngrid,nlay) ! Geometric mean radius used for stormdust (m)
99!                                    !   CCNs (m)
100      real r0topdust(ngrid,nlay) ! Geometric mean radius used for topdust (m)
101!                                    !   CCNs (m)
102      real,save :: beta ! correction for the shape of the ice particles (cf. newsedim)
103c     for ice radius computation
104      REAL Mo,No
105      REAl ccntyp
106      character(len=20),parameter :: modname="callsedim"
107
108
109c     Discrete size distributions (doubleq)
110c     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
111c       1) Parameters used to represent the changes in fall
112c          velocity as a function of particle size;
113      integer ir
114      integer,parameter :: nr=12 !(nr=7) ! number of bins
115      real,save :: rd(nr)
116      real qr(ngrid,nlay,nr)
117      real,save :: rdi(nr+1)    ! extreme and intermediate radii
118      real Sq(ngrid,nlay)
119      real,parameter :: rdmin=1.e-8
120      real,parameter :: rdmax=30.e-6
121      real,parameter :: rdimin=1.e-8 ! 1.e-7
122      real,parameter :: rdimax=1.e-4
123
124c       2) Second size distribution for the log-normal integration
125c          (the mass mixing ratio is computed for each radius)
126
127      integer iint
128      integer,parameter :: ninter=4 ! number of points between each rdi radii
129      real,save :: rr(ninter,nr)
130      integer radpower
131      real sigma0
132
133c       3) Other local variables used in doubleq
134
135      INTEGER,SAVE :: idust_mass  ! index of tracer containing dust mass
136                                  !   mix. ratio
137      INTEGER,SAVE :: idust_number ! index of tracer containing dust number
138                                   !   mix. ratio
139      INTEGER,SAVE :: iccn_mass  ! index of tracer containing CCN mass
140                                 !   mix. ratio
141      INTEGER,SAVE :: iccn_number ! index of tracer containing CCN number
142                                  !   mix. ratio
143      INTEGER,SAVE :: istormdust_mass  !  index of tracer containing
144                                       !stormdust mass mix. ratio
145      INTEGER,SAVE :: istormdust_number !  index of tracer containing
146                                        !stormdust number mix. ratio
147      INTEGER,SAVE :: itopdust_mass  !  index of tracer containing
148                                       !topdust mass mix. ratio
149      INTEGER,SAVE :: itopdust_number !  index of tracer containing
150                                        !topdust number mix. ratio                       
151      INTEGER,SAVE :: iccnco2_number ! index of tracer containing CCN number
152      INTEGER,SAVE :: iccnco2_mass ! index of tracer containing CCN number
153      INTEGER,SAVE :: ico2_ice ! index of tracer containing CCN number
154
155
156      LOGICAL,SAVE :: firstcall=.true.
157
158
159
160c    ** un petit test de coherence
161c       --------------------------
162      ! AS: firstcall OK absolute
163      IF (firstcall) THEN
164         
165c       Doubleq: initialization
166        IF (doubleq) THEN
167         do ir=1,nr
168             rd(ir)= rdmin*(rdmax/rdmin)**(float(ir-1)/float(nr-1))
169         end do
170         rdi(1)=rdimin
171         do ir=2,nr
172           rdi(ir)= sqrt(rd(ir-1)*rd(ir))
173         end do
174         rdi(nr+1)=rdimax
175
176         do ir=1,nr
177           do iint=1,ninter
178             rr(iint,ir)=
179     &        rdi(ir)*
180     &        (rdi(ir+1)/rdi(ir))**(float(iint-1)/float(ninter-1))
181c             write(*,*) rr(iint,ir)
182           end do
183         end do
184
185      ! identify tracers corresponding to mass mixing ratio and
186      ! number mixing ratio
187        idust_mass=0      ! dummy initialization
188        idust_number=0    ! dummy initialization
189
190        do iq=1,nq
191          if (noms(iq).eq."dust_mass") then
192            idust_mass=iq
193            write(*,*)"callsedim: idust_mass=",idust_mass
194          endif
195          if (noms(iq).eq."dust_number") then
196            idust_number=iq
197            write(*,*)"callsedim: idust_number=",idust_number
198          endif
199        enddo
200
201        ! check that we did find the tracers
202        if ((idust_mass.eq.0).or.(idust_number.eq.0)) then
203          write(*,*) 'callsedim: error! could not identify'
204          write(*,*) ' tracers for dust mass and number mixing'
205          write(*,*) ' ratio and doubleq is activated!'
206          call abort_physic(modname,"missing dust tracers",1)
207        endif
208        ENDIF !of if (doubleq)
209
210        IF (microphys) THEN
211          iccn_mass=0
212          iccn_number=0
213          do iq=1,nq
214            if (noms(iq).eq."ccn_mass") then
215              iccn_mass=iq
216              write(*,*)"callsedim: iccn_mass=",iccn_mass
217            endif
218            if (noms(iq).eq."ccn_number") then
219              iccn_number=iq
220              write(*,*)"callsedim: iccn_number=",iccn_number
221            endif
222          enddo
223          ! check that we did find the tracers
224          if ((iccn_mass.eq.0).or.(iccn_number.eq.0)) then
225            write(*,*) 'callsedim: error! could not identify'
226            write(*,*) ' tracers for ccn mass and number mixing'
227            write(*,*) ' ratio and microphys is activated!'
228            call abort_physic(modname,"missing ccn tracers",1)
229          endif
230        ENDIF !of if (microphys)
231
232        IF (co2clouds) THEN
233          iccnco2_mass=0
234          iccnco2_number=0
235          ico2_ice=0
236          do iq=1,nq
237            if (noms(iq).eq."ccnco2_mass") then
238              iccnco2_mass=iq
239              write(*,*)"callsedim: iccnco2_mass=",iccnco2_mass
240            endif
241            if (noms(iq).eq."co2_ice") then
242              ico2_ice=iq
243              write(*,*)"callsedim: ico2_ice=",ico2_ice
244            endif
245            if (noms(iq).eq."ccnco2_number") then
246              iccnco2_number=iq
247              write(*,*)"callsedim: iccnco2_number=",iccnco2_number
248            endif
249          enddo
250          ! check that we did find the tracers
251          if ((iccnco2_mass.eq.0).or.(iccnco2_number.eq.0)) then
252            write(*,*) 'callsedim: error! could not identify'
253            write(*,*) ' tracers for ccn co2 mass and number mixing'
254            write(*,*) ' ratio and co2clouds are activated!'
255            call abort_physic(modname,"missing co2 ccn tracers",1)
256          endif
257       ENDIF                    !of if (co2clouds)
258
259       IF (water) THEN
260         write(*,*) "correction for the shape of the ice particles ?"
261         beta=0.75 ! default value
262         call getin_p("ice_shape",beta)
263         write(*,*) " ice_shape = ",beta
264
265          write(*,*) "water_param nueff Sedimentation:", nuice_sed
266          IF (activice) THEN
267            write(*,*) "water_param nueff Radiative:", nuice_ref
268          ENDIF
269       ENDIF
270
271       IF (rdstorm) THEN ! identifying stormdust tracers for sedimentation
272           istormdust_mass=0      ! dummy initialization
273           istormdust_number=0    ! dummy initialization
274
275           do iq=1,nq
276             if (noms(iq).eq."stormdust_mass") then
277               istormdust_mass=iq
278               write(*,*)"callsedim: istormdust_mass=",istormdust_mass
279             endif
280             if (noms(iq).eq."stormdust_number") then
281               istormdust_number=iq
282               write(*,*)"callsedim: istormdust_number=",
283     &                                           istormdust_number
284             endif
285           enddo
286
287           ! check that we did find the tracers
288           if ((istormdust_mass.eq.0).or.(istormdust_number.eq.0)) then
289             write(*,*) 'callsedim: error! could not identify'
290             write(*,*) ' tracers for stormdust mass and number mixing'
291             write(*,*) ' ratio and rdstorm is activated!'
292             call abort_physic(modname,"missing stormdust tracers",1)
293           endif
294       ENDIF !of if (rdstorm)
295
296       IF (slpwind) THEN ! identifying topdust tracers for sedimentation
297           itopdust_mass=0      ! dummy initialization
298           itopdust_number=0    ! dummy initialization
299
300           do iq=1,nq
301             if (noms(iq).eq."topdust_mass") then
302               itopdust_mass=iq
303               write(*,*)"callsedim: itopdust_mass=",itopdust_mass
304             endif
305             if (noms(iq).eq."topdust_number") then
306               itopdust_number=iq
307               write(*,*)"callsedim: itopdust_number=",
308     &                                           itopdust_number
309             endif
310           enddo
311
312           ! check that we did find the tracers
313           if ((itopdust_mass.eq.0).or.(itopdust_number.eq.0)) then
314             write(*,*) 'callsedim: error! could not identify'
315             write(*,*) ' tracers for topdust mass and number mixing'
316             write(*,*) ' ratio and slpwind is activated!'
317             call abort_physic(modname,"missing topdust tracers",1)
318           endif
319       ENDIF !of if (slpwind)
320
321        firstcall=.false.
322      ENDIF ! of IF (firstcall)
323
324c-----------------------------------------------------------------------
325c    1. Initialization
326c    -----------------
327
328!      zqi(1:ngrid,1:nlay,1:nqmx) = 0.
329c     Update the mass mixing ratio and temperature with the tendencies coming
330c       from other parameterizations:
331c     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
332      zqi(1:ngrid,1:nlay,1:nq)=pq(1:ngrid,1:nlay,1:nq)
333     &                         +pdqfi(1:ngrid,1:nlay,1:nq)*ptimestep
334      zt(1:ngrid,1:nlay)=pt(1:ngrid,1:nlay)
335     &                         +pdt(1:ngrid,1:nlay)*ptimestep
336
337c    Computing the different layer properties
338c    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
339c    Mass (kg.m-2), thickness(m), crossing time (s)  etc.
340
341      do  l=1,nlay
342        do ig=1, ngrid
343          masse(ig,l)=(pplev(ig,l) - pplev(ig,l+1)) /g
344          epaisseur(ig,l)= zlev(ig,l+1) - zlev(ig,l)
345        end do
346      end do
347
348c =================================================================
349c     Compute the geometric mean radius used for sedimentation
350
351      if (doubleq) then
352        do l=1,nlay
353          do ig=1, ngrid
354     
355         call updaterdust(zqi(ig,l,igcm_dust_mass),
356     &                    zqi(ig,l,igcm_dust_number),r0dust(ig,l),
357     &                    tauscaling(ig))
358         
359          end do
360        end do
361      endif
362c     rocket dust storm
363      if (rdstorm) then
364        do l=1,nlay
365          do ig=1, ngrid
366     
367         call updaterdust(zqi(ig,l,igcm_stormdust_mass),
368     &               zqi(ig,l,igcm_stormdust_number),r0stormdust(ig,l),
369     &               tauscaling(ig))
370         
371          end do
372        end do
373      endif
374c     entrainment by slope wind
375      if (slpwind) then
376        do l=1,nlay
377          do ig=1, ngrid
378     
379         call updaterdust(zqi(ig,l,igcm_topdust_mass),
380     &               zqi(ig,l,igcm_topdust_number),r0topdust(ig,l),
381     &               tauscaling(ig))
382         
383          end do
384        end do
385      endif
386c =================================================================
387      do iq=1,nq
388        if(radius(iq).gt.1.e-9 .and.(iq.ne.ico2_ice) .and.
389     &        (iq .ne. iccnco2_mass) .and. (iq .ne.
390     &        iccnco2_number)) then   ! no sedim for gaz or CO2 clouds  (done in microtimestep)
391
392c -----------------------------------------------------------------
393c         DOUBLEQ CASE
394c -----------------------------------------------------------------
395          if ( doubleq.and.
396     &     ((iq.eq.idust_mass).or.(iq.eq.idust_number).or.
397     &     (iq.eq.istormdust_mass).or.(iq.eq.istormdust_number).or.
398     &     (iq.eq.itopdust_mass).or.(iq.eq.itopdust_number)) ) then
399     
400c           Computing size distribution:
401c           ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
402
403            if ((iq.eq.idust_mass).or.(iq.eq.idust_number)) then
404              do  l=1,nlay
405                do ig=1, ngrid
406                  r0(ig,l)=r0dust(ig,l)
407                end do
408              end do
409            else if ((iq.eq.istormdust_mass).or.
410     &                                (iq.eq.istormdust_number)) then
411              do  l=1,nlay
412                do ig=1, ngrid
413                  r0(ig,l)=r0stormdust(ig,l)
414                end do
415              end do
416            else if ((iq.eq.itopdust_mass).or.
417     &                                (iq.eq.itopdust_number)) then
418              do  l=1,nlay
419                do ig=1, ngrid
420                  r0(ig,l)=r0topdust(ig,l)
421                end do
422              end do
423            endif
424            sigma0 = varian
425
426c        Computing mass mixing ratio for each particle size
427c        ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
428          IF ((iq.EQ.idust_mass).or.(iq.EQ.istormdust_mass)
429     &                          .or.(iq.EQ.itopdust_mass)) then
430            radpower = 2
431          ELSE  ! number
432            radpower = -1
433          ENDIF
434          Sq(1:ngrid,1:nlay) = 0.
435          do ir=1,nr
436            do l=1,nlay
437              do ig=1,ngrid
438c                ****************
439c                Size distribution integration
440c                (Trapezoid Integration Method)
441                 qr(ig,l,ir)=0.5*(rr(2,ir)-rr(1,ir))*
442     &             (rr(1,ir)**radpower)*
443     &             exp(-(log(rr(1,ir)/r0(ig,l)))**2/(2*sigma0**2))
444                 do iint=2,ninter-1
445                   qr(ig,l,ir)=qr(ig,l,ir) +
446     &             0.5*(rr(iint+1,ir)-rr(iint-1,ir))*
447     &             (rr(iint,ir)**radpower)*
448     &             exp(-(log(rr(iint,ir)/r0(ig,l)))**2/
449     &             (2*sigma0**2))
450                 end do
451                 qr(ig,l,ir)=qr(ig,l,ir) +
452     &             0.5*(rr(ninter,ir)-rr(ninter-1,ir))*
453     &             (rr(ninter,ir)**radpower)*
454     &             exp(-(log(rr(ninter,ir)/r0(ig,l)))**2/
455     &             (2*sigma0**2))
456
457c                **************** old method (not recommended!)
458c                qr(ig,l,ir)=(rd(ir)**(5-3*iq))*
459c    &           exp( -(log(rd(ir)/r0(ig,l)))**2 / (2*sigma0**2) )
460c                ******************************
461
462                 Sq(ig,l)=Sq(ig,l)+qr(ig,l,ir)
463              enddo
464            enddo
465          enddo
466
467          do ir=1,nr
468            do l=1,nlay
469              do ig=1,ngrid
470                 qr(ig,l,ir) = zqi(ig,l,iq)*qr(ig,l,ir)/Sq(ig,l)
471              enddo
472            enddo
473          enddo
474
475c         Computing sedimentation for each tracer
476c         ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
477
478          zqi(1:ngrid,1:nlay,iq) = 0.
479          pdqs_sed(1:ngrid,iq) = 0.
480
481          do ir=1,nr
482               call newsedim(ngrid,nlay,1,1,ptimestep,
483     &         pplev,masse,epaisseur,zt,rd(ir),(/rho_dust/),qr(1,1,ir),
484     &         wq,0.5)
485
486c            Tendencies
487c            ~~~~~~~~~~
488             do ig=1,ngrid
489               pdqs_sed(ig,iq) = pdqs_sed(ig,iq)
490     &                                + wq(ig,1)/ptimestep
491             end do
492             DO l = 1, nlay
493               DO ig=1,ngrid
494                 zqi(ig,l,iq)=zqi(ig,l,iq)+qr(ig,l,ir)
495               ENDDO
496             ENDDO           
497          enddo ! of do ir=1,nr
498c -----------------------------------------------------------------
499c         WATER CYCLE CASE
500c -----------------------------------------------------------------
501           else if ((iq .eq. iccn_mass) .or. (iq .eq. iccn_number)
502     &       .or. (iq .eq. igcm_h2o_ice)
503     &       .or. (iq .eq. igcm_hdo_ice)) then
504            if (microphys) then
505              ! water ice sedimentation
506              call newsedim(ngrid,nlay,ngrid*nlay,ngrid*nlay,
507     &        ptimestep,pplev,masse,epaisseur,zt,rsedcloud,rhocloud,
508     &        zqi(1,1,iq),wq,beta)
509            else
510              ! water ice sedimentation
511              call newsedim(ngrid,nlay,ngrid*nlay,1,
512     &        ptimestep,pplev,masse,epaisseur,zt,rsedcloud,rho_q(iq),
513     &        zqi(1,1,iq),wq,beta)
514            endif ! of if (microphys)
515c           Tendencies
516c           ~~~~~~~~~~
517            do ig=1,ngrid
518              pdqs_sed(ig,iq)=wq(ig,1)/ptimestep
519            end do
520c -----------------------------------------------------------------
521c         GENERAL CASE
522c -----------------------------------------------------------------
523          else
524            call newsedim(ngrid,nlay,1,1,ptimestep,
525     &      pplev,masse,epaisseur,zt,radius(iq),rho_q(iq),
526     &      zqi(1,1,iq),wq,1.0)
527c           Tendencies
528c           ~~~~~~~~~~
529            do ig=1,ngrid
530              pdqs_sed(ig,iq)=wq(ig,1)/ptimestep
531            end do
532          endif ! of if doubleq and if water
533c -----------------------------------------------------------------
534
535c         Compute the final tendency:
536c         ---------------------------
537          DO l = 1, nlay
538            DO ig=1,ngrid
539              pdqsed(ig,l,iq)=(zqi(ig,l,iq)-
540     $        (pq(ig,l,iq) + pdqfi(ig,l,iq)*ptimestep))/ptimestep
541            ENDDO
542          ENDDO
543
544        endif ! of if(radius(iq).gt.1.e-9)
545c =================================================================
546      enddo ! of do iq=1,nq
547
548c     Update the dust particle size "rdust"
549c     -------------------------------------
550      if (doubleq) then
551       DO l = 1, nlay
552        DO ig=1,ngrid
553       
554     
555         call updaterdust(zqi(ig,l,igcm_dust_mass),
556     &                    zqi(ig,l,igcm_dust_number),rdust(ig,l),
557     &                    tauscaling(ig))     
558
559         
560        ENDDO
561       ENDDO
562      endif ! of if (doubleq)
563
564      if (rdstorm) then
565       DO l = 1, nlay
566        DO ig=1,ngrid
567         call updaterdust(zqi(ig,l,igcm_stormdust_mass),
568     &                zqi(ig,l,igcm_stormdust_number),rstormdust(ig,l),
569     &                tauscaling(ig))   
570        ENDDO
571       ENDDO
572      endif ! of if (rdstorm)
573
574      if (slpwind) then
575       DO l = 1, nlay
576        DO ig=1,ngrid
577         call updaterdust(zqi(ig,l,igcm_topdust_mass),
578     &                zqi(ig,l,igcm_topdust_number),rtopdust(ig,l),
579     &                tauscaling(ig))   
580        ENDDO
581       ENDDO
582      endif ! of if (slpwind)
583 
584c     Update the ice particle size "rice"
585c     -------------------------------------
586      if (water) then
587       IF(microphys) THEN
588       
589       
590        DO l = 1, nlay
591          DO ig=1,ngrid
592
593         call updaterice_micro(zqi(ig,l,igcm_h2o_ice),
594     &    zqi(ig,l,igcm_ccn_mass),zqi(ig,l,igcm_ccn_number),
595     &    tauscaling(ig),rice(ig,l),rhocloud(ig,l))
596           
597          ENDDO
598        ENDDO
599       
600       ELSE
601       
602        DO l = 1, nlay
603          DO ig=1,ngrid
604         
605            call updaterice_typ(zqi(ig,l,igcm_h2o_ice),
606     &                      tau(ig,1),zlay(ig,l),rice(ig,l))
607
608          ENDDO
609        ENDDO
610       ENDIF ! of IF(microphys)
611      endif ! of if (water)
612
613      END SUBROUTINE callsedim
614     
615      END MODULE callsedim_mod
616
Note: See TracBrowser for help on using the repository browser.