source: trunk/LMDZ.VENUS/libf/phyvenus/phytrac_relax.F @ 1240

Last change on this file since 1240 was 1160, checked in by slebonnois, 11 years ago

SL: update for tracers management in phytrac, Venus

File size: 8.2 KB
Line 
1!
2! $Header: /home/cvsroot/LMDZ4/libf/phylmd/phytrac.F,v 1.16 2006/03/24 15:06:23 lmdzadmin Exp $
3!
4c
5c
6      SUBROUTINE phytrac_relax (debutphy,lafin,
7     I                    nqmax,
8     I                    nlon,
9     I                    nlev,
10     I                    pdtphys,
11     I                    pplay,
12     O                    tr_seri)
13
14c======================================================================
15c Auteur(s) FH
16c Objet: Moniteur general des tendances traceurs
17c
18cAA Remarques en vrac:
19cAA--------------------
20cAA 1/ le call phytrac se fait avec nqmax
21c
22c SL: Janvier 2014
23c Version developed by E. Marcq for pseudo-chemistry relaxation
24c See Marcq&Lebonnois 2013.
25c
26c======================================================================
27      USE ioipsl
28      USE infotrac
29      USE control_mod
30      use dimphy
31      USE comgeomphy
32      IMPLICIT none
33#include "YOMCST.h"
34#include "dimensions.h"
35#include "clesphys.h"
36#include "temps.h"
37#include "paramet.h"
38c======================================================================
39
40c Arguments:
41
42c   EN ENTREE:
43c   ==========
44
45      logical debutphy       ! le flag de l'initialisation de la physique
46      logical lafin          ! le flag de la fin de la physique
47      integer nqmax ! nombre de traceurs auxquels on applique la physique
48      integer nlon  ! nombre de points horizontaux
49      integer nlev  ! nombre de couches verticales
50      real pdtphys  ! pas d'integration pour la physique (seconde)
51      real pplay(nlon,nlev)  ! pression pour le mileu de chaque couche (en Pa)
52
53c   EN ENTREE/SORTIE:
54c   =================
55
56      real tr_seri(nlon,nlev,nqmax) ! traceur 
57
58cAA ----------------------------
59cAA  VARIABLES LOCALES TRACEURS
60cAA ----------------------------
61
62C les traceurs
63
64c===================
65c it--------indice de traceur
66c k,i---------indices long, vert
67c===================
68c Variables deja declarees dont on a besoin pour traceurs   
69c   k,i,it,tr_seri(nlon,nlev,nqmax),pplay(nlon,nlev),
70      integer nqCO_OCS
71c      real pzero,gamma
72c      parameter (pzero=85000.)
73c      parameter (gamma=5000.)
74      REAL alpha
75      real deltatr(nlon,nlev,nqtot) ! ecart au profil de ref zprof
76      real,save,allocatable :: zprof(:,:)
77      real,save,allocatable :: tau(:,:) ! temps de relaxation vers le profil (s)
78c======================================================================
79
80      INTEGER i, k, it
81
82c Variables liees a l'ecriture de la bande histoire physique
83
84c Variables locales pour effectuer les appels en serie
85c----------------------------------------------------
86
87      REAL d_tr(nlon,nlev) ! tendances de traceurs
88
89      character*20 modname
90      character*80 abort_message
91
92c======================================================================
93
94      modname = 'phytrac_relax'
95c TRACEURS TYPE CO ET OCS
96      nqCO_OCS   = 6
97
98c---------
99c debutphy
100c---------
101      if (debutphy) then
102         print*,"DEBUT PHYTRAC"
103         print*,"PHYTRAC: RELAXATION"
104         allocate(zprof(nlev,nqtot),tau(nlev,nqtot))
105
106c=============================================================
107c=============================================================
108c=============================================================
109c   Initialisation des traceurs
110c=============================================================
111c=============================================================
112c=============================================================
113
114C=========================================================================
115C=========================================================================
116
117c II) Declaration d'un profil vertical de traceur OK
118c
119c zprof   = profil de rappel
120c
121c 1 -> CO ; 2 -> OCS
122c def des profils en log(a) = a * log(P) + b par morceaux, cf. pollack et al
123c tr_seri en ppm
124c (initialisation seulement si ceux-ci sont nuls)
125
126c ICI, ON UTILISE 3 CONSTANTES DE TEMPS DIFFERENTES POUR CHAQUE,
127c DONC TRACEURS 1 A 3 POUR CO ET 4 A 6 POUR OCS
128C=========================================================================
129
130
131c Constantes de rappel:
132
133       print*,"INIT TAU"
134       do k=1,nlev
135         tau(k,1)=1.e6
136         tau(k,2)=1.e7
137         tau(k,3)=1.e8
138         tau(k,4)=1.e6
139         tau(k,5)=1.e7
140         tau(k,6)=1.e8
141       enddo
142
143c CO
144
145      do it=1,3
146       print*,"INIT ZPROF ",tname(it)
147       do k=1,nlev
148         zprof(k,it)=0.
149c pour l'instant, tau fixe, mais possibilite de le faire varier avec z
150        if (pplay(nlon/2,k) >= 4.8e6) then
151           zprof(k,it)=14.
152        endif
153        if ((pplay(nlon/2,k)<=4.8e6).and.(pplay(nlon/2,k)>=1.9e6)) then
154           alpha=(log(pplay(nlon/2,k))-log(1.9e6))/
155     .     (log(4.8e6)-log(1.9e6))
156           zprof(k,it)=20.*(14./20.)**alpha
157        endif
158        if ((pplay(nlon/2,k)<=1.9e6).and.(pplay(nlon/2,k)>=1.5e5)) then
159           alpha=(log(pplay(nlon/2,k))-log(1.5e5))/
160     .     (log(1.9e6)-log(1.5e5))
161           zprof(k,it)=39.*(20./39.)**alpha
162        endif
163        if ((pplay(nlon/2,k)<=1.5e5).and.(pplay(nlon/2,k)>=1.1e4)) then
164           alpha=(log(pplay(nlon/2,k))-log(1.1e4))/
165     .     (log(2.73e5)-log(1.1e4))
166           zprof(k,it)=50.*(39./50.)**alpha
167        endif
168        if ((pplay(nlon/2,k)<=1.1e4).and.(pplay(nlon/2,k)>=1.3e3)) then
169           alpha=(log(pplay(nlon/2,k))-log(1.3e3))/
170     .     (log(1.1e4)-log(1.3e3))
171           zprof(k,it)=2.*(50./2.)**alpha
172        endif
173        if ((pplay(nlon/2,k)<=1.3e3).and.(pplay(nlon/2,k)>=2.4)) then
174           alpha=(log(pplay(nlon/2,k))-log(2.4))/
175     .     (log(1.3e3)-log(2.4))
176           zprof(k,it)=1000.*(2./1000.)**alpha
177        endif
178        if (pplay(nlon/2,k) <= 2.4) then
179           zprof(k,it)=1000.
180        endif
181       enddo
182       print*,zprof(:,it)
183 
184c OCS
185       print*,"INIT ZPROF ",tname(it+3)
186       do k=1,nlev
187         zprof(k,it+3)=0.
188         if (pplay(nlon/2,k) >= 4.8e6) then
189           zprof(k,it+3)=30.
190         endif
191         if ((pplay(nlon/2,k)<=4.8e6).and.(pplay(nlon/2,k)>=9.4e5))
192     *   then
193           alpha=(log(pplay(nlon/2,k))-log(9.4e5))/
194     *     (log(4.8e6)-log(9.4e5))
195           zprof(k,it+3)=20.*(30/20.)**alpha
196         endif
197         if ((pplay(nlon/2,k)<=9.4e5).and.(pplay(nlon/2,k)>=4.724e5))
198     *   then
199           alpha=(log(pplay(nlon/2,k))-log(4.724e5))/
200     *     (log(9.4e5)-log(4.724e5))
201           zprof(k,it+3)=0.5*(20/0.5)**alpha
202         endif
203         if ((pplay(nlon/2,k)<=4.724e5).and.(pplay(nlon/2,k)>=1.1e4))
204     *   then
205           alpha=(log(pplay(nlon/2,k))-log(1.1e4))/
206     *     (log(4.724e5)-log(1.1e4))
207           zprof(k,it+3)=0.005*(0.5/0.005)**alpha
208         endif
209         if (pplay(nlon/2,k)<=1.1e4) then
210           zprof(k,it+3)=0.
211         endif
212       end do
213       print*,zprof(:,it+3)
214      enddo
215
216c Initialisation du traceur s'il est nul:
217       do it=1,nqCO_OCS
218        if ((tr_seri(nlon/2,1,it).eq.0.).and.
219     .      (tr_seri(nlon/2,nlev/2,it).eq.0.).and.
220     .      (tr_seri(nlon/2,nlev,it).eq.0.)) then
221         print*,"INITIALISATION DE ",tname(it)
222         do k=1,nlev
223           do i=1,nlon
224             tr_seri(i,k,it) = zprof(k,it)
225           enddo
226         enddo
227        endif
228       enddo
229
230C=========================================================================
231C=========================================================================
232
233c-------------
234c fin debutphy
235c-------------
236      ENDIF  ! fin debutphy
237
238c======================================================================
239c Rappel vers un profil
240c======================================================================
241         do it=1,nqCO_OCS
242           do k=1,nlev
243             do i=1,nlon
244c VERIF
245           if (tr_seri(i,k,it).lt.0) then
246             print*,"Traceur negatif AVANT rappel:",i,k,it
247             stop
248           endif
249c FIN VERIF
250
251           deltatr(i,k,it) = (-tr_seri(i,k,it)+zprof(k,it))/tau(k,it)
252           tr_seri(i,k,it) =  tr_seri(i,k,it) + deltatr(i,k,it)*pdtphys
253
254c VERIF
255           if (tr_seri(i,k,it).lt.0) then
256             print*,"APRES rappel:",i,k,it,
257     .  deltatr(i,k,it),zprof(k,it),tr_seri(i,k,it),pdtphys/tau(k,it)
258             stop
259           endif
260c FIN VERIF
261             enddo
262           enddo
263         enddo
264
265c======================================================================
266c======================================================================
267
268
269      RETURN
270      END
271     
272     
Note: See TracBrowser for help on using the repository browser.