source: trunk/LMDZ.GENERIC/libf/phystd/callsedim.F @ 146

Last change on this file since 146 was 135, checked in by aslmd, 14 years ago

CHANGEMENT ARBORESCENCE ETAPE 2 -- NON COMPLET

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