source: trunk/MESOSCALE/LMDZ.MARS/libf_gcm/phymars/callsedim.F @ 134

Last change on this file since 134 was 57, checked in by aslmd, 14 years ago

mineur LMD_MM_MARS: ajout du GCM ancienne physique, systeme maintenant complet sur SVN (ne manque que la base de donnees d'etats initiaux)

File size: 4.4 KB
Line 
1      SUBROUTINE callsedim(ngrid,nlay, ptimestep,
2     $                pplev,zlev, pt,
3     &                pq, pdqfi, pdqsed,pdqs_sed,nq)
4      IMPLICIT NONE
5
6c=======================================================================
7c      Sedimentation of the  Martian aerosols
8c      depending on their density and radius
9c
10c      F.Forget 1999
11c
12c=======================================================================
13
14c-----------------------------------------------------------------------
15c   declarations:
16c   -------------
17
18#include "dimensions.h"
19#include "dimphys.h"
20#include "comcstfi.h"
21#include "tracer.h"
22#include "callkeys.h"
23
24#include "fisice.h"
25c
26c   arguments:
27c   ----------
28
29      INTEGER ngrid,nlay
30      REAL ptimestep            ! pas de temps physique (s)
31      REAL pplev(ngrid,nlay+1)   ! pression aux inter-couches (Pa)
32      REAL pt(ngrid,nlay)    ! temperature au centre des couches (K)
33      REAL zlev(ngrid,nlay+1) ! altitude at layer boundaries
34
35
36c    Traceurs :
37      integer nq             ! nombre de traceurs
38      real pq(ngrid,nlay,nq)  ! traceur (kg/kg)
39      real pdqfi(ngrid,nlay,nq)  ! tendance avant sedimentation (kg/kg.s-1)
40      real pdqsed(ngrid,nlay,nq) ! tendande due a la sedimentation (kg/kg.s-1)
41      real pdqs_sed(ngrid,nq)    ! flux en surface (kg.m-2.s-1)
42     
43c   local:
44c   ------
45
46      INTEGER l,ig, iq
47
48      real zqi(ngridmx,nlayermx)
49      real masse (ngridmx,nlayermx)
50      real epaisseur (ngridmx,nlayermx)
51      real wq(ngridmx,nlayermx+1)
52c      real dens(ngridmx,nlayermx) ! Mean density of the ice part. accounting for dust core
53      real rfall(ngridmx,nlayermx)
54
55
56      LOGICAL firstcall
57      SAVE firstcall
58      DATA firstcall/.true./
59
60c    ** un petit test de coherence
61c       --------------------------
62
63      IF (firstcall) THEN
64         IF(ngrid.NE.ngridmx) THEN
65            PRINT*,'STOP dans coefdifv'
66            PRINT*,'probleme de dimensions :'
67            PRINT*,'ngrid  =',ngrid
68            PRINT*,'ngridmx  =',ngridmx
69            STOP
70         ENDIF
71         firstcall=.false.
72      ENDIF
73
74c-----------------------------------------------------------------------
75c    1. initialisation
76c    -----------------
77c
78c     Calcul preliminaires  de caracteristiques des couches
79c     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
80c    Masse (kg.m-2), epaisseur(m), temps de traversee (s)  etc...
81
82
83      do  l=1,nlay
84        do ig=1, ngrid
85          masse(ig,l)=(pplev(ig,l) - pplev(ig,l+1)) /g
86          epaisseur(ig,l)= zlev(ig,l+1) - zlev(ig,l)
87        end do
88      end do
89
90      do iq=1, nq
91
92        if(radius(iq).gt.1.e-9) then   ! no sedim for gaz (defined by radius=0)
93
94c         On "update" la valeur de q apres les autres parametrisations
95c         ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
96
97          do l=1,nlay
98            do ig=1,ngrid
99              zqi(ig,l)=pq(ig,l,iq)+pdqfi(ig,l,iq)*ptimestep
100              if (iceparty.and.iq.eq.nq-1) then
101c               On affecte un rayon moyen aux poussieres a chaque altitude du type :
102c               r(z)=r0*exp(-z/H) avec r0=0.8 micron et H=18 km.
103c               ''''''''''''''''''''''''''''''''''''''''''''''''
104                rfall(ig,l)=max( rice(ig,l)*1.5,rdust(ig,l) )
105c modif FranckMM pour ameliorer cycle H2O: rfall= 20 microns
106                rfall(ig,l)=min(rfall(ig,l),1.e-4)
107!mars commente pour l'instant               rfall(ig,l)=20.e-6
108               
109              endif
110            enddo
111          enddo
112
113c         Calcul du transport par sedimentation pour chaque traceur
114c         ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
115          if(iceparty.and.iq.eq.nq-1) then
116            call newsedim(ngrid,nlay,ngrid*nlay,ptimestep,
117     &      pplev,masse,epaisseur,pt,rfall,rho_q(iq),zqi,wq)
118          else
119            call newsedim(ngrid,nlay,1,ptimestep,
120     &      pplev,masse,epaisseur,pt,radius(iq),rho_q(iq),zqi,wq)
121          endif
122
123c         Calcul des tendances
124c         ~~~~~~~~~~~~~~~~~~~~
125          do ig=1,ngrid
126            if(iceparty.and.iq.eq.nq-1) then
127                pdqs_sed(ig,nq) = wq(ig,1)/ptimestep
128            else
129                pdqs_sed(ig,iq) = wq(ig,1)/ptimestep
130            endif
131          end do
132          DO l = 1, nlay
133            DO ig=1,ngrid
134c             zqi(ig,l)=max(zqi(ig,l), 1.e-10)
135              pdqsed(ig,l,iq)=(zqi(ig,l)-
136     $        (pq(ig,l,iq) + pdqfi(ig,l,iq)*ptimestep))/ptimestep
137            ENDDO
138          ENDDO
139        endif
140      enddo
141 
142      RETURN
143      END
144
Note: See TracBrowser for help on using the repository browser.