source: trunk/LMDZ.PLUTO/libf/phypluto/callsedim_pluto.F90 @ 3586

Last change on this file since 3586 was 3585, checked in by debatzbr, 13 days ago

Connecting microphysics to radiative transfer + miscellaneous cleans

File size: 5.3 KB
Line 
1      SUBROUTINE callsedim_pluto(ngrid,nlay, ptimestep, &
2                     pplev,zlev,pt,pdt,rice_ch4,rice_co, &
3                     pq, pdqfi, pdqsed,pdqs_sed,nq,pphi)
4
5      use tracer_h, only: igcm_ch4_ice,igcm_co_ice,radius,rho_q
6      use comcstfi_mod, only:  g
7      IMPLICIT NONE
8!==================================================================
9!
10!     Purpose
11!     -------
12!     Calculates sedimentation of aerosols depending on their
13!     density and radius.
14!
15!     Authors
16!     -------
17!     F. Forget (1999)
18!     Tracer generalisation by E. Millour (2009)
19!
20!==================================================================
21
22!-----------------------------------------------------------------------
23!   declarations:
24!   -------------
25
26!
27!   arguments:
28!   ----------
29
30      INTEGER ngrid              ! number of horizontal grid points
31      INTEGER nlay               ! number of atmospheric layers
32      REAL ptimestep             ! physics time step (s)
33      REAL pplev(ngrid,nlay+1)   ! pressure at inter-layers (Pa)
34      REAL pt(ngrid,nlay)        ! temperature at mid-layer (K)
35      REAL pdt(ngrid,nlay)       ! tendency on temperature
36      REAL zlev(ngrid,nlay+1)    ! altitude at layer boundaries
37      REAL pphi(ngrid,nlay)      ! geopotential
38
39
40!    Traceurs :
41      integer nq             ! number of tracers
42      real pq(ngrid,nlay,nq)  ! tracers (kg/kg)
43      real pdqfi(ngrid,nlay,nq)  ! tendency before sedimentation (kg/kg.s-1)
44      real pdqsed(ngrid,nlay,nq) ! tendency due to sedimentation (kg/kg.s-1)
45      real pdqs_sed(ngrid,nq)    ! flux at surface (kg.m-2.s-1)
46
47!   local:
48!   ------
49
50      INTEGER l,ig, iq
51
52      real zqi(ngrid,nlay) ! to locally store tracers
53      real zt(ngrid,nlay) ! to locally store temperature (K)
54      real masse (ngrid,nlay) ! Layer mass (kg.m-2)
55      real epaisseur (ngrid,nlay) ! Layer thickness (m)
56      real wq(ngrid,nlay+1) ! displaced tracer mass (kg.m-2)
57      real rfall_ch4(ngrid,nlay)
58      real rfall_co(ngrid,nlay)
59      real rice_ch4(ngrid,nlay)
60      real rice_co(ngrid,nlay)
61
62      LOGICAL firstcall
63      SAVE firstcall
64      DATA firstcall/.true./
65
66!    ** un petit test de coherence
67!       --------------------------
68
69      IF (firstcall) THEN
70         IF(ngrid.NE.ngrid) THEN
71            PRINT*,'STOP dans callsedim'
72            PRINT*,'probleme de dimensions :'
73            PRINT*,'ngrid  =',ngrid
74            PRINT*,'ngrid  =',ngrid
75            STOP
76         ENDIF
77
78        firstcall=.false.
79      ENDIF ! of IF (firstcall)
80
81!=======================================================================
82!     Preliminary calculation of the layer characteristics
83!     (mass (kg.m-2), thickness (m), etc.
84
85      do  l=1,nlay
86        do ig=1, ngrid
87          masse(ig,l)=(pplev(ig,l) - pplev(ig,l+1)) /g
88          epaisseur(ig,l)= zlev(ig,l+1) - zlev(ig,l)
89          zt(ig,l)=pt(ig,l)+pdt(ig,l)*ptimestep
90        end do
91      end do
92
93      do iq=1,nq
94        if(radius(iq).gt.1.e-12) then   ! no sedimentation for gases (defined by radius=0)
95!     Radius values are defined in initracer
96!     The value of q is updated after the other parameterisations
97
98          do l=1,nlay
99            do ig=1,ngrid
100              ! store locally updated tracers
101              zqi(ig,l)=pq(ig,l,iq)+pdqfi(ig,l,iq)*ptimestep
102
103!                cf sur Mars:
104!                On affecte un rayon moyen aux poussieres a chaque altitude du type :
105!                r(z)=r0*exp(-z/H) avec r0=0.8 micron et H=18 km.
106!                rfall(ig,l)=max( rice(ig,l)*1.5,rdust(ig,l) )
107!                Pluton : choix de rfall a la place de radius
108              if (iq.eq.igcm_ch4_ice) then
109                 ! TB: rfall_ch4(ig,l)=max( rice_ch4(ig,l)*1.5,2.e-7)
110                 rfall_ch4(ig,l)=max( rice_ch4(ig,l),2.e-7)
111                 rfall_ch4(ig,l)=min(rfall_ch4(ig,l),1.e-4)
112              endif
113              if (iq.eq.igcm_co_ice) then
114                 rfall_co(ig,l)=max( rice_co(ig,l),2.e-7)
115                 rfall_co(ig,l)=min(rfall_co(ig,l),1.e-4)
116              endif
117            enddo
118          enddo ! of do l=1,nlay
119
120!=======================================================================
121!     Calculate the transport due to sedimentation for each tracer
122
123          if (iq.eq.igcm_ch4_ice) then
124          !if (iceparty.and.(iq.eq.igcm_ch4_ice)) then
125            call newsedim_pluto(ngrid,nlay,ngrid*nlay,ptimestep, &
126           pplev,masse,epaisseur,zt,rfall_ch4,rho_q(iq),zqi,wq,pphi)
127          else if (iq.eq.igcm_co_ice) then
128            call newsedim_pluto(ngrid,nlay,ngrid*nlay,ptimestep, &
129           pplev,masse,epaisseur,zt,rfall_co,rho_q(iq),zqi,wq,pphi)
130          else if ((radius(iq).gt.0.)) then   ! haze tracers
131            call newsedim_pluto(ngrid,nlay,1,ptimestep, &
132           pplev,masse,epaisseur,zt,radius(iq),rho_q(iq),zqi,wq,pphi)
133          endif
134
135!=======================================================================
136!     Calculate the tendencies
137
138          do ig=1,ngrid
139!     Ehouarn: with new way of tracking tracers by name, this is simply
140            pdqs_sed(ig,iq)=wq(ig,1)/ptimestep
141          end do
142
143          DO l = 1, nlay
144            DO ig=1,ngrid
145              pdqsed(ig,l,iq)=(zqi(ig,l)- &
146             (pq(ig,l,iq) + pdqfi(ig,l,iq)*ptimestep))/ptimestep
147            ENDDO
148          ENDDO
149
150        endif ! of if(radius(iq).gt.1.e-12)
151      enddo ! of do iq=1,nq
152
153      RETURN
154      END
155
Note: See TracBrowser for help on using the repository browser.