source: trunk/LMDZ.TITAN/libf/phytitan/sources.F @ 524

Last change on this file since 524 was 474, checked in by slebonnois, 13 years ago

Update of Titan physics for clouds.

File size: 6.7 KB
RevLine 
[175]1         SUBROUTINE sources(ngrid,nlay,
2     $                      ptimestep,pz0,pu,pv,
3     $                      pplev,pzlay,pzlev,
4     $                      gaz1,gaz2,gaz3,
[474]5     $                      ptsrf,evapch4,reserv)
[175]6
7c=======================================================================
8c     Calcul des flux aux interfaces pour les sources
9c     CH4 a la surface
10c     Production de C2H6 en haut du modele.
11c     Production de C2H2 en haut du modele.
12c     
13c     NOTE :
14c     Les gaz ont la tete en haut.
15c     ils ne suivent pas la meme convention que muphys :
16c     (1 -> sol  / klev = haut du modele)
17c=======================================================================
18
19c-----------------------------------------------------------------------
20c   declarations:
21c   -------------
22
23         use dimphy
24         IMPLICIT NONE
25#include "dimensions.h"
26#include "microtab.h"
27#include "YOMCST.h"
28c
29c   arguments:
30c   ----------
31
32         INTEGER ngrid,nlay,nq,ihor
33         REAL ptimestep
34         REAL pplev(ngrid,nlay+1)
35         REAL pzlay(ngrid,nlay),pzlev(ngrid,nlay+1)
36         REAL pu(ngrid),pv(ngrid)
37         REAL gaz1(ngrid,nlay),gaz2(ngrid,nlay),gaz3(ngrid,nlay)
38         REAL ptsrf(ngrid)
[474]39         REAL evapch4(ngrid)
[175]40c
41c   local:
42c   ------
43 
44         INTEGER ilev,ig,ilay,nlev,k,inch4,inc2h6
45
46         REAL zgz1(klon,klev),zgz2(klon,klev),zgz3(klon,klev)
47         REAL zcdv(klon),zu2,pz0
48         REAL xmair,gg,zrho,ws,ch,qch4,flux
49         REAL xmuair
50         REAL zmem,zmem2,zmem3
51         REAL prodc2h6,prodc2h2
52         real reserv(ngrid),restemp,drestemp
[474]53         REAL zevapch4
[175]54
55         real umin
56         data umin/1.e-12/
57         save umin
58c
[474]59c
[175]60c-----------------------------------------------------------------------
61c   initialisations:
62c   -----------------
63
64         nlev=nlay+1
65
66         if(nlay.ne.klev) THEN
67           PRINT*,'STOP dans sources.F'
68           PRINT*,'probleme de dimensions :'
69           PRINT*,'nlay  =',nlay
70           PRINT*,'klev  =',klev
71           STOP
72         endif
73
74         IF(ngrid.NE.klon) THEN
75           PRINT*,'STOP dans sources.F'
76           PRINT*,'probleme de dimensions :'
77           PRINT*,'ngrid  =',ngrid
78           PRINT*,'klon  =',klon
79           STOP
80         ENDIF
81
82         zgz1 = gaz1
83         zgz2 = gaz2
84         zgz3 = gaz3
85
[474]86         evapch4 = 0.
87
[175]88c-----------------------------------------------------------------------
89c     2. calcul de  cd :
90c     ----------------
91c
92         DO ig=1,ngrid
93           zu2=pu(ig)*pu(ig)+pv(ig)*pv(ig)+umin
94           zcdv(ig)=pz0*(1.+sqrt(zu2))
95c           write(99,'(I4,3(ES24.17,1X))') ig,
96c     &     pz0,zu2,(1.+sqrt(zu2))
97         ENDDO
98c          write(99,*) ""
99
100c-----------------------------------------------------------------------
101c    4. Conditions aux limites pour CH4 et C2H6
102c    -------------------------------------------
103c
104
105*   Conditions CH4
106         DO ig=1,ngrid
[474]107           zevapch4=0.
[175]108           restemp=0.
109           gg=RG*RA**2/(RA+pzlay(ig,1))**2.
110           zrho=(pplev(ig,1)-pplev(ig,2))/gg
111           zrho=zrho/(pzlev(ig,2)-pzlev(ig,1))
112           ws=sqrt(pu(ig)**2.+pv(ig)**2.)*(10./pzlay(ig,1))**0.2
113           ch=1.5*sqrt(zcdv(ig))
114           call ch4sat(ptsrf(ig),pplev(ig,1),qch4) ! qch4=kg/kg
115           qch4=qch4*0.50 ! ici on impose 50% d'humidité au sol
116       
117           if(reserv(ig).le. 1.e-10 ) then 
118             flux=0.
119             reserv(ig)=1.e-10
120           else
121             flux=zrho*ch*ws
122             flux=flux*0.1 ! fraction occupée par les lacs
123           endif
124
125           zmem=zgz1(ig,1)
126           zgz1(ig,1)=(zgz1(ig,1)+flux*ptimestep*qch4*28./16.)
127     &                /(1.+flux*ptimestep)
128
129           gg=RG!*RA**2/(RA+pzlay(ig,1))**2.
130           xmair=(pplev(ig,1)-pplev(ig,1+1))/gg
131           xmair=xmair/(pzlev(ig,1+1)-pzlev(ig,1))
132           xmuair=28.!*(1.-zmem)+zmem*16.
133
134           drestemp = - (zgz1(ig,1)-zmem)*xmair ! en m3/m2=m
135     &     *(pzlev(ig,2)-pzlev(ig,1))*16./xmuair/425.
136
137c           ici on peut fixer un seuil sur drestemp
138c           (ie limiter l'echange atm/surface)
139     
140           restemp=reserv(ig) +drestemp
141
142           IF (restemp.ge.0.) THEN
143             reserv(ig) = reserv(ig) + drestemp
[474]144             zevapch4   = zevapch4   + drestemp
[175]145           ELSE
146*          Il n'y a pas suffisamment de méthane; on re-évalue le flux d'évaporation
147*          Quelle nouvelle concentration zgz1(ig,1) atteint-on en évaporant tout ?
[474]148             zgz1(ig,1)= reserv(ig)/(xmair*(pzlev(ig,1+1)-pzlev(ig,1))
[175]149     &                 *16./xmuair/425.)+zmem
[474]150             zevapch4  = zevapch4-reserv(ig)
[175]151
152             if(reserv(ig).eq.0.)
153     &       print*,'assechement du sol en ig=', ig,reserv(ig),flux
154
155             reserv(ig)=0.  ! on a tout évaporé...
156           ENDIF
157c         
[474]158           evapch4(ig)=evapch4(ig)+zevapch4  ! evapch4 doit etre < 0
[175]159
160         ENDDO
[474]161
[175]162*   Conditions C2H6
163
164         prodc2h6=6.e-12/5. ! kg/m2/s
165 
166         IF (1.EQ.1) THEN
167           DO ig=1,ngrid
168             DO ilev=nlay,nlay-4,-1
169*            calcule de zrho (kg/m3) pour la couche...
170               gg=RG*RA**2/(RA+pzlay(ig,ilev))**2.
171               zrho=(pplev(ig,ilev)-pplev(ig,ilev+1))/gg
172               zrho=zrho/(pzlev(ig,ilev+1)-pzlev(ig,ilev))
173
174*              passage taux de production --> Dx_c2h6 a rajouter au niveau ilev
175               zmem2=zgz2(ig,ilev)
176               zgz2(ig,ilev)=zgz2(ig,ilev)+
177     &         prodc2h6*ptimestep/
178     &         abs(pzlev(ig,ilev+1)-pzlev(ig,ilev))    !  kg/m3/s
179     &         /zrho*28./30.
180
181             ENDDO
182           ENDDO
183
184         ELSE
185
186           DO ig=1,ngrid
187             DO ilev=nlay,nlay-8,-1
188               zgz2(ig,ilev)=1.2e-5
189             ENDDO
190           ENDDO
191
192         ENDIF  ! (fin 1.eq.0)
193
194*-------------------------------------
195*   Conditions C2H2
196
197         prodc2h2=1.6e-12/5. ! kg/m2/s
198
199         IF(1  .EQ.  1) THEN
200
201           DO ig=1,ngrid
202             DO ilev=nlay,nlay-4,-1
203*            calcule de zrho (kg/m3) pour la couche...
204                gg=RG*RA**2/(RA+pzlay(ig,ilev))**2.
205                zrho=(pplev(ig,ilev)-pplev(ig,ilev+1))/gg
206                zrho=zrho/(pzlev(ig,ilev+1)-pzlev(ig,ilev))
207
208*            passage taux de production --> Dx_c2h2 a rajouter au niveau ilev
209                zmem3=zgz3(ig,ilev)
210                zgz3(ig,ilev)=zgz3(ig,ilev)+
211     &          (prodc2h2)*ptimestep/
212     &          abs(pzlev(ig,ilev+1)-pzlev(ig,ilev))  !  kg/m3/s
213     &          /zrho*28./26.
214
215             ENDDO
216
217           ENDDO
218
219         ENDIF
220
221c-----------------------------------------------------------------------
222         DO ig=1,ngrid
223           DO ilev=1,nlay
224             gaz1(ig,ilev)=zgz1(ig,ilev)
225             gaz2(ig,ilev)=zgz2(ig,ilev)
226             gaz3(ig,ilev)=zgz3(ig,ilev)
227           ENDDO
228         ENDDO
229
230        RETURN
231        END
Note: See TracBrowser for help on using the repository browser.