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

Last change on this file since 2214 was 2199, checked in by mvals, 6 years ago

Mars GCM:
Implementation of a new parametrization of the dust entrainment by slope winds above the sub-grid scale topography. The parametrization is activated with the flag slpwind=.true. (set to "false" by
default) in callphys.def. The new parametrization involves the new tracers topdust_mass and topdust_number.
MV

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