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

Last change on this file since 1545 was 1543, checked in by emillour, 10 years ago

All models: Further adaptations to keep up with changes in LMDZ5 concerning
physics/dynamics separation:

  • dyn3d:
  • adapted gcm.F so that all physics initializations are now done in iniphysiq.
  • dyn3dpar:
  • adapted gcm.F so that all physics initializations are now done in iniphysiq.
  • updated calfis_p.F to follow up with changes.
  • copied over updated "bands.F90" from LMDZ5.
  • dynphy_lonlat:
  • calfis_p.F90, mod_interface_dyn_phys.F90, follow up of changes in phy_common/mod_* routines
  • phy_common:
  • added "geometry_mod.F90" to store information about the grid (replaces phy*/comgeomphy.F90) and give variables friendlier names: rlond => longitude , rlatd => latitude, airephy => cell_area, cuphy => dx , cvphy => dy
  • added "physics_distribution_mod.F90"
  • updated "mod_grid_phy_lmdz.F90", "mod_phys_lmdz_mpi_data.F90", "mod_phys_lmdz_para.F90", "mod_phys_lmdz_mpi_transfert.F90", "mod_grid_phy_lmdz.F90", "mod_phys_lmdz_omp_data.F90", "mod_phys_lmdz_omp_transfert.F90", "write_field_phy.F90" and "ioipsl_getin_p_mod.F90" to LMDZ5 versions.
  • phy[venus/titan/mars/std]:
  • removed "init_phys_lmdz.F90", "comgeomphy.F90"; adapted routines to use geometry_mod (longitude, latitude, cell_area, etc.)

EM

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