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

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