/[lmdze]/trunk/phylmd/phytrac.f
ViewVC logotype

Annotation of /trunk/phylmd/phytrac.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 15 - (hide annotations)
Fri Aug 1 15:24:12 2008 UTC (15 years, 9 months ago) by guez
Original Path: trunk/libf/phylmd/phytrac.f90
File size: 23772 byte(s)
-- Minor modification of input/output:

Added variable "Sigma_O3_Royer" to "histday.nc". "ecrit_day" is not
modified in "physiq". Removed variables "pyu1", "pyv1", "ftsol1",
"ftsol2", "ftsol3", "ftsol4", "psrf1", "psrf2", "psrf3", "psrf4"
"mfu", "mfd", "en_u", "en_d", "de_d", "de_u", "coefh" from
"histrac.nc".

Variable "raz_date" of module "conf_gcm_m" has logical type instead of
integer type.

-- Should not change any result at run time:

Modified calls to "IOIPSL_Lionel" procedures because the interfaces of
these procedures have been simplified.

Changed name of variable in module "start_init_orog_m": "masque" to
"mask".

Created a module containing procedure "phyredem".

Removed arguments "punjours", "pdayref" and "ptimestep" of procedure
"iniphysiq".

Renamed procedure "gr_phy_write" to "gr_phy_write_2d". Created
procedure "gr_phy_write_3d".

Removed procedures "ini_undefstd", "moy_undefSTD", "calcul_STDlev",
"calcul_divers".

1 guez 3 module phytrac_m
2    
3     ! This module is clean: no C preprocessor directive, no include line.
4    
5     IMPLICIT none
6    
7     private
8     public phytrac
9    
10     contains
11    
12 guez 7 SUBROUTINE phytrac(rnpb, itap, lmt_pas, julien, gmtime, firstcal, lafin, &
13     nqmax, pdtphys, u, v, t_seri, paprs, pplay, pmfu, pmfd, pen_u, &
14 guez 3 pde_u, pen_d, pde_d, coefh, fm_therm, entr_therm, yu1, yv1, ftsol, &
15     pctsrf, frac_impa, frac_nucl, presnivs, pphis, &
16 guez 12 pphi, albsol, rh, cldfra, rneb, diafra, cldliq, itop_con, &
17 guez 3 ibas_con, pmflxr, pmflxs, prfl, psfl, da, phi, mp, upwd, dnwd, tr_seri)
18    
19     ! From phylmd/phytrac.F, version 1.15 2006/02/21 08:08:30
20    
21     ! Authors : Frédéric Hourdin, Abderrahmane Idelkadi, Marie-Alice
22     ! Foujols, Olivia
23     ! Objet : moniteur général des tendances des traceurs
24    
25     ! Remarques :
26     ! 1/ L'appel de "phytrac" se fait avec "nq-2" donc nous avons bien
27     ! les vrais traceurs (en nombre "nbtr", sans la vapeur d'eau ni l'eau
28     ! liquide) dans "phytrac".
29     ! 2/ Le choix du radon et du plomb se fait juste avec un "data"
30     ! (peu propre).
31     ! Pourrait-on avoir une variable qui indiquerait le type de traceur ?
32    
33     use dimens_m, only: iim, jjm, llm
34     use indicesol, only: nbsrf
35     use dimphy, only: klon, nbtr
36 guez 12 use clesphys, only: ecrit_tra
37     use clesphys2, only: iflag_con
38 guez 3 use abort_gcm_m, only: abort_gcm
39     use YOMCST, only: rg
40     use ctherm, only: iflag_thermals
41 guez 7 use regr_pr_comb_coefoz_m, only: regr_pr_comb_coefoz
42 guez 3 use phyetat0_m, only: rlat
43     use o3_chem_m, only: o3_chem
44    
45     ! Arguments:
46    
47     ! EN ENTREE:
48    
49     ! divers:
50    
51     logical, intent(in):: rnpb
52    
53     integer, intent(in):: nqmax
54     ! (nombre de traceurs auxquels on applique la physique)
55    
56 guez 7 integer, intent(in):: itap ! number of calls to "physiq"
57     integer, intent(in):: lmt_pas ! number of time steps of "physics" per day
58 guez 3 integer, intent(in):: julien !jour julien, 1 <= julien <= 360
59     integer itop_con(klon)
60     integer ibas_con(klon)
61     real, intent(in):: gmtime ! heure de la journée en fraction de jour
62 guez 7 real, intent(in):: pdtphys ! pas d'integration pour la physique (s)
63 guez 3 real, intent(in):: t_seri(klon, llm) ! temperature, in K
64    
65     real tr_seri(klon, llm, nbtr)
66     ! (mass fractions of tracers, excluding water, at mid-layers)
67    
68     real u(klon, llm)
69     real v(klon, llm)
70     real rh(klon, llm) ! humidite relative
71     real cldliq(klon, llm) ! eau liquide nuageuse
72     real cldfra(klon, llm) ! fraction nuageuse (tous les nuages)
73    
74     real diafra(klon, llm)
75     ! (fraction nuageuse (convection ou stratus artificiels))
76    
77     real rneb(klon, llm) ! fraction nuageuse (grande echelle)
78     real albsol(klon) ! albedo surface
79    
80     real, intent(in):: paprs(klon, llm+1)
81     ! (pression pour chaque inter-couche, en Pa)
82    
83 guez 10 real, intent(in):: pplay(klon, llm)
84     ! (pression pour le mileu de chaque couche, en Pa)
85    
86 guez 3 real pphi(klon, llm) ! geopotentiel
87     real pphis(klon)
88     REAL, intent(in):: presnivs(llm)
89 guez 7 logical, intent(in):: firstcal ! first call to "calfis"
90 guez 3 logical, intent(in):: lafin ! fin de la physique
91    
92     integer nsplit
93     REAL pmflxr(klon, llm+1), pmflxs(klon, llm+1) !--lessivage convection
94     REAL prfl(klon, llm+1), psfl(klon, llm+1) !--lessivage large-scale
95    
96     ! convection:
97    
98     REAL pmfu(klon, llm) ! flux de masse dans le panache montant
99     REAL pmfd(klon, llm) ! flux de masse dans le panache descendant
100     REAL pen_u(klon, llm) ! flux entraine dans le panache montant
101    
102     ! thermiques:
103    
104     real fm_therm(klon, llm+1), entr_therm(klon, llm)
105    
106     REAL pde_u(klon, llm) ! flux detraine dans le panache montant
107     REAL pen_d(klon, llm) ! flux entraine dans le panache descendant
108     REAL pde_d(klon, llm) ! flux detraine dans le panache descendant
109     ! KE
110     real da(klon, llm), phi(klon, llm, llm), mp(klon, llm)
111     REAL upwd(klon, llm) ! saturated updraft mass flux
112     REAL dnwd(klon, llm) ! saturated downdraft mass flux
113    
114     ! Couche limite:
115    
116     REAL coefh(klon, llm) ! coeff melange CL
117     REAL yu1(klon) ! vents au premier niveau
118     REAL yv1(klon) ! vents au premier niveau
119    
120     ! Lessivage:
121    
122     ! pour le ON-LINE
123    
124     REAL frac_impa(klon, llm) ! fraction d'aerosols impactes
125     REAL frac_nucl(klon, llm) ! fraction d'aerosols nuclees
126    
127     ! Arguments necessaires pour les sources et puits de traceur:
128    
129     real ftsol(klon, nbsrf) ! Temperature du sol (surf)(Kelvin)
130     real pctsrf(klon, nbsrf) ! Pourcentage de sol f(nature du sol)
131    
132     real pftsol1(klon), pftsol2(klon), pftsol3(klon), pftsol4(klon)
133     real ppsrf1(klon), ppsrf2(klon), ppsrf3(klon), ppsrf4(klon)
134    
135     ! VARIABLES LOCALES TRACEURS
136    
137     ! Sources et puits des traceurs:
138    
139     ! Pour l'instant seuls les cas du rn et du pb ont ete envisages.
140    
141     REAL source(klon) ! a voir lorsque le flux est prescrit
142     !
143     ! Pour la source de radon et son reservoir de sol
144    
145     REAL, save:: trs(klon, nbtr) ! Concentration de radon dans le sol
146    
147     REAL masktr(klon, nbtr) ! Masque reservoir de sol traceur
148     ! Masque de l'echange avec la surface
149     ! (1 = reservoir) ou (possible => 1 )
150     SAVE masktr
151     REAL fshtr(klon, nbtr) ! Flux surfacique dans le reservoir de sol
152     SAVE fshtr
153     REAL hsoltr(nbtr) ! Epaisseur equivalente du reservoir de sol
154     SAVE hsoltr
155     REAL tautr(nbtr) ! Constante de decroissance radioactive
156     SAVE tautr
157     REAL vdeptr(nbtr) ! Vitesse de depot sec dans la couche Brownienne
158     SAVE vdeptr
159     REAL scavtr(nbtr) ! Coefficient de lessivage
160     SAVE scavtr
161    
162     CHARACTER itn
163     INTEGER, save:: nid_tra
164    
165     ! nature du traceur
166    
167     logical aerosol(nbtr) ! Nature du traceur
168     ! ! aerosol(it) = true => aerosol
169     ! ! aerosol(it) = false => gaz
170     logical clsol(nbtr) ! couche limite sol calculée
171     logical radio(nbtr) ! décroisssance radioactive
172     save aerosol, clsol, radio
173    
174     ! convection tiedtke
175     INTEGER i, k, it
176     REAL delp(klon, llm)
177    
178     ! Variables liees a l'ecriture de la bande histoire physique
179    
180     ! Variables locales pour effectuer les appels en serie
181    
182     REAL d_tr(klon, llm), d_trs(klon) ! tendances de traceurs
183     REAL d_tr_cl(klon, llm, nbtr) ! tendance de traceurs couche limite
184     REAL d_tr_cv(klon, llm, nbtr) ! tendance de traceurs conv pour chq traceur
185     REAL d_tr_th(klon, llm, nbtr) ! la tendance des thermiques
186     REAL d_tr_dec(klon, llm, 2) ! la tendance de la decroissance
187     ! ! radioactive du rn - > pb
188     REAL d_tr_lessi_impa(klon, llm, nbtr) ! la tendance du lessivage
189     ! ! par impaction
190     REAL d_tr_lessi_nucl(klon, llm, nbtr) ! la tendance du lessivage
191     ! ! par nucleation
192     REAL flestottr(klon, llm, nbtr) ! flux de lessivage
193     ! ! dans chaque couche
194    
195     real zmasse(klon, llm)
196     ! (column-density of mass of air in a layer, in kg m-2)
197    
198     real ztra_th(klon, llm)
199    
200     character(len=20) modname
201     character(len=80) abort_message
202     integer isplit
203    
204     ! Controls:
205     logical:: couchelimite = .true.
206     logical:: convection = .true.
207     logical:: lessivage = .true.
208     logical, save:: inirnpb
209    
210     !--------------------------------------
211    
212     modname='phytrac'
213    
214 guez 7 if (firstcal) then
215 guez 3 print *, 'phytrac: pdtphys = ', pdtphys
216     PRINT *, 'Fréquence de sortie des traceurs : ecrit_tra = ', ecrit_tra
217     if (nbtr < nqmax) then
218     abort_message='See above'
219     call abort_gcm(modname, abort_message, 1)
220     endif
221     inirnpb=rnpb
222    
223     ! Initialisation des sorties :
224     call ini_histrac(nid_tra, pdtphys, presnivs, nqmax, lessivage)
225    
226     ! Initialisation de certaines variables pour le radon et le plomb
227     ! Initialisation du traceur dans le sol (couche limite radonique)
228     trs(:, :) = 0.
229    
230     open (unit=99, file='starttrac', status='old', err=999, &
231     form='formatted')
232     read(unit=99, fmt=*) (trs(i, 1), i=1, klon)
233     999 continue
234     close(unit=99)
235    
236     ! Initialisation de la fraction d'aerosols lessivee
237    
238     d_tr_lessi_impa(:, :, :) = 0.
239     d_tr_lessi_nucl(:, :, :) = 0.
240    
241     ! Initialisation de la nature des traceurs
242    
243     DO it = 1, nqmax
244     aerosol(it) = .FALSE. ! Tous les traceurs sont des gaz par defaut
245     radio(it) = .FALSE. ! par défaut pas de passage par "radiornpb"
246     clsol(it) = .FALSE. ! Par defaut couche limite avec flux prescrit
247     ENDDO
248     ENDIF
249    
250     ! Initialisation du traceur dans le sol (couche limite radonique)
251     if (inirnpb) THEN
252    
253     radio(1)= .true.
254     radio(2)= .true.
255     clsol(1)= .true.
256     clsol(2)= .true.
257     aerosol(2) = .TRUE. ! le Pb est un aerosol
258    
259     call initrrnpb(ftsol, pctsrf, masktr, fshtr, hsoltr, tautr, vdeptr, &
260     scavtr)
261     inirnpb=.false.
262     endif
263    
264     do i=1, klon
265     pftsol1(i) = ftsol(i, 1)
266     pftsol2(i) = ftsol(i, 2)
267     pftsol3(i) = ftsol(i, 3)
268     pftsol4(i) = ftsol(i, 4)
269    
270     ppsrf1(i) = pctsrf(i, 1)
271     ppsrf2(i) = pctsrf(i, 2)
272     ppsrf3(i) = pctsrf(i, 3)
273     ppsrf4(i) = pctsrf(i, 4)
274    
275     enddo
276    
277     ! Calcul de l'effet de la convection
278    
279     if (convection) then
280     DO it=1, nqmax
281     if (iflag_con.eq.2) then
282     ! tiedke
283     CALL nflxtr(pdtphys, pmfu, pmfd, pen_u, pde_u, pen_d, pde_d, &
284 guez 10 paprs, tr_seri(1, 1, it), d_tr_cv(1, 1, it))
285 guez 3 else if (iflag_con.eq.3) then
286     ! KE
287 guez 10 call cvltr(pdtphys, da, phi, mp, paprs, &
288 guez 3 tr_seri(1, 1, it), upwd, dnwd, d_tr_cv(1, 1, it))
289     endif
290    
291     DO k = 1, llm
292     DO i = 1, klon
293     tr_seri(i, k, it) = tr_seri(i, k, it) + d_tr_cv(i, k, it)
294     ENDDO
295     ENDDO
296     WRITE(unit=itn, fmt='(i1)') it
297     CALL minmaxqfi(tr_seri(:, :, it), 0., 1.e33, &
298     'convection, tracer index = ' // itn)
299     ENDDO
300     endif
301    
302     forall (k=1: llm) zmasse(:, k) = (paprs(:, k)-paprs(:, k+1)) / rg
303    
304     ! Calcul de l'effet des thermiques
305    
306     do it=1, nqmax
307     do k=1, llm
308     do i=1, klon
309     d_tr_th(i, k, it)=0.
310     tr_seri(i, k, it)=max(tr_seri(i, k, it), 0.)
311     tr_seri(i, k, it)=min(tr_seri(i, k, it), 1.e10)
312     enddo
313     enddo
314     enddo
315    
316     if (iflag_thermals > 0) then
317     nsplit=10
318     DO it=1, nqmax
319     do isplit=1, nsplit
320     ! Thermiques
321     call dqthermcell(klon, llm, pdtphys/nsplit &
322     , fm_therm, entr_therm, zmasse &
323     , tr_seri(1:klon, 1:llm, it), d_tr, ztra_th)
324    
325     do k=1, llm
326     do i=1, klon
327     d_tr(i, k)=pdtphys*d_tr(i, k)/nsplit
328     d_tr_th(i, k, it)=d_tr_th(i, k, it)+d_tr(i, k)
329     tr_seri(i, k, it)=max(tr_seri(i, k, it)+d_tr(i, k), 0.)
330     enddo
331     enddo
332     enddo
333     ENDDO
334     endif
335    
336     ! Calcul de l'effet de la couche limite
337    
338     if (couchelimite) then
339    
340     DO k = 1, llm
341     DO i = 1, klon
342     delp(i, k) = paprs(i, k)-paprs(i, k+1)
343     ENDDO
344     ENDDO
345    
346     ! MAF modif pour tenir compte du cas rnpb + traceur
347     DO it=1, nqmax
348     if (clsol(it)) then
349     ! couche limite avec quantite dans le sol calculee
350     CALL cltracrn(it, pdtphys, yu1, yv1, &
351     coefh, t_seri, ftsol, pctsrf, &
352     tr_seri(1, 1, it), trs(1, it), &
353     paprs, pplay, delp, &
354     masktr(1, it), fshtr(1, it), hsoltr(it), &
355     tautr(it), vdeptr(it), &
356     rlat, &
357     d_tr_cl(1, 1, it), d_trs)
358     DO k = 1, llm
359     DO i = 1, klon
360     tr_seri(i, k, it) = tr_seri(i, k, it) + d_tr_cl(i, k, it)
361     ENDDO
362     ENDDO
363    
364     ! Traceur ds sol
365    
366     DO i = 1, klon
367     trs(i, it) = trs(i, it) + d_trs(i)
368     END DO
369     else ! couche limite avec flux prescrit
370     !MAF provisoire source / traceur a creer
371     DO i=1, klon
372     source(i) = 0.0 ! pas de source, pour l'instant
373     ENDDO
374    
375     CALL cltrac(pdtphys, coefh, t_seri, &
376     tr_seri(1, 1, it), source, &
377     paprs, pplay, delp, &
378     d_tr_cl(1, 1, it))
379     DO k = 1, llm
380     DO i = 1, klon
381     tr_seri(i, k, it) = tr_seri(i, k, it) + d_tr_cl(i, k, it)
382     ENDDO
383     ENDDO
384     endif
385     ENDDO
386    
387     endif ! couche limite
388    
389     ! Calcul de l'effet du puits radioactif
390    
391     ! MAF il faudrait faire une modification pour passer dans radiornpb
392     ! si radio=true mais pour l'instant radiornpb propre au cas rnpb
393     if (rnpb) then
394     d_tr_dec(:, :, :) = radiornpb(tr_seri, pdtphys, tautr)
395     DO it=1, nqmax
396     if (radio(it)) then
397     tr_seri(:, :, it) = tr_seri(:, :, it) + d_tr_dec(:, :, it)
398     WRITE(unit=itn, fmt='(i1)') it
399     CALL minmaxqfi(tr_seri(:, :, it), 0., 1.e33, 'puits rn it='//itn)
400     endif
401     ENDDO
402     endif ! rnpb decroissance radioactive
403    
404 guez 6 if (nqmax >= 3) then
405     ! Ozone as a tracer:
406 guez 7 if (mod(itap - 1, lmt_pas) == 0) then
407     ! Once per day, update the coefficients for ozone chemistry:
408     call regr_pr_comb_coefoz(julien)
409     end if
410 guez 6 call o3_chem(julien, gmtime, t_seri, zmasse, pdtphys, tr_seri(:, :, 3))
411     end if
412 guez 3
413     ! Calcul de l'effet de la precipitation
414    
415     IF (lessivage) THEN
416     d_tr_lessi_nucl(:, :, :) = 0.
417     d_tr_lessi_impa(:, :, :) = 0.
418     flestottr(:, :, :) = 0.
419    
420     ! tendance des aerosols nuclees et impactes
421    
422     DO it = 1, nqmax
423     IF (aerosol(it)) THEN
424     DO k = 1, llm
425     DO i = 1, klon
426     d_tr_lessi_nucl(i, k, it) = d_tr_lessi_nucl(i, k, it) + &
427     ( 1 - frac_nucl(i, k) )*tr_seri(i, k, it)
428     d_tr_lessi_impa(i, k, it) = d_tr_lessi_impa(i, k, it) + &
429     ( 1 - frac_impa(i, k) )*tr_seri(i, k, it)
430     ENDDO
431     ENDDO
432     ENDIF
433     ENDDO
434    
435     ! Mises a jour des traceurs + calcul des flux de lessivage
436     ! Mise a jour due a l'impaction et a la nucleation
437    
438     DO it = 1, nqmax
439     IF (aerosol(it)) THEN
440     DO k = 1, llm
441     DO i = 1, klon
442     tr_seri(i, k, it)=tr_seri(i, k, it) &
443     *frac_impa(i, k)*frac_nucl(i, k)
444     ENDDO
445     ENDDO
446     ENDIF
447     ENDDO
448    
449     ! Flux lessivage total
450    
451     DO it = 1, nqmax
452     DO k = 1, llm
453     DO i = 1, klon
454     flestottr(i, k, it) = flestottr(i, k, it) - &
455     ( d_tr_lessi_nucl(i, k, it) + &
456     d_tr_lessi_impa(i, k, it) ) * &
457     ( paprs(i, k)-paprs(i, k+1) ) / &
458     (RG * pdtphys)
459     ENDDO
460     ENDDO
461     ENDDO
462     ENDIF
463    
464     ! Ecriture des sorties
465 guez 7 call write_histrac(lessivage, nqmax, itap, nid_tra)
466 guez 3
467     if (lafin) then
468     print *, "C'est la fin de la physique."
469     open (unit=99, file='restarttrac', form='formatted')
470     do i=1, klon
471     write(unit=99, fmt=*) trs(i, 1)
472     enddo
473     PRINT *, 'Ecriture du fichier restarttrac'
474     close(99)
475     endif
476    
477     contains
478    
479 guez 7 subroutine write_histrac(lessivage, nqmax, itap, nid_tra)
480 guez 3
481     ! From phylmd/write_histrac.h, version 1.9 2006/02/21 08:08:30
482    
483     use dimens_m, only: iim, jjm, llm
484     use ioipsl, only: histwrite, histsync
485     use temps, only: itau_phy
486     use advtrac_m, only: tnom
487     use comgeomphy, only: airephy
488     use dimphy, only: klon
489    
490     logical, intent(in):: lessivage
491    
492     integer, intent(in):: nqmax
493     ! (nombre de traceurs auxquels on applique la physique)
494    
495 guez 7 integer, intent(in):: itap ! number of calls to "physiq"
496 guez 3 integer, intent(in):: nid_tra
497    
498     ! Variables local to the procedure:
499     INTEGER ndex2d(iim*(jjm+1)), ndex3d(iim*(jjm+1)*llm)
500     integer it
501     integer itau_w ! pas de temps ecriture
502     REAL zx_tmp_2d(iim, jjm+1), zx_tmp_3d(iim, jjm+1, llm)
503     logical, parameter:: ok_sync = .true.
504    
505     !-----------------------------------------------------
506    
507     ndex2d = 0
508     ndex3d = 0
509 guez 7 itau_w = itau_phy + itap
510 guez 3
511     CALL gr_fi_ecrit(1, klon, iim, jjm+1, pphis, zx_tmp_2d)
512 guez 15 CALL histwrite(nid_tra, "phis", itau_w, zx_tmp_2d)
513 guez 3
514     CALL gr_fi_ecrit(1, klon, iim, jjm+1, airephy, zx_tmp_2d)
515 guez 15 CALL histwrite(nid_tra, "aire", itau_w, zx_tmp_2d)
516 guez 3
517     CALL gr_fi_ecrit(llm, klon, iim, jjm+1, zmasse, zx_tmp_3d)
518 guez 15 CALL histwrite(nid_tra, "zmasse", itau_w, zx_tmp_3d)
519 guez 3
520     DO it=1, nqmax
521     CALL gr_fi_ecrit(llm, klon, iim, jjm+1, tr_seri(1, 1, it), zx_tmp_3d)
522 guez 15 CALL histwrite(nid_tra, tnom(it+2), itau_w, zx_tmp_3d)
523 guez 3 if (lessivage) THEN
524     CALL gr_fi_ecrit(llm, klon, iim, jjm+1, flestottr(1, 1, it), &
525     zx_tmp_3d)
526 guez 15 CALL histwrite(nid_tra, "fl"//tnom(it+2), itau_w, zx_tmp_3d)
527 guez 3 endif
528    
529     CALL gr_fi_ecrit(llm, klon, iim, jjm+1, d_tr_th(1, 1, it), zx_tmp_3d)
530 guez 15 CALL histwrite(nid_tra, "d_tr_th_"//tnom(it+2), itau_w, zx_tmp_3d)
531 guez 3 CALL gr_fi_ecrit(llm, klon, iim, jjm+1, d_tr_cv(1, 1, it), zx_tmp_3d)
532 guez 15 CALL histwrite(nid_tra, "d_tr_cv_"//tnom(it+2), itau_w, zx_tmp_3d)
533 guez 3 CALL gr_fi_ecrit(llm, klon, iim, jjm+1, d_tr_cl(1, 1, it), zx_tmp_3d)
534 guez 15 CALL histwrite(nid_tra, "d_tr_cl_"//tnom(it+2), itau_w, zx_tmp_3d)
535 guez 3 ENDDO
536    
537     CALL gr_fi_ecrit(llm, klon, iim, jjm+1, pplay, zx_tmp_3d)
538 guez 15 CALL histwrite(nid_tra, "pplay", itau_w, zx_tmp_3d)
539 guez 3
540     CALL gr_fi_ecrit(llm, klon, iim, jjm+1, t_seri, zx_tmp_3d)
541 guez 15 CALL histwrite(nid_tra, "t", itau_w, zx_tmp_3d)
542 guez 3
543     if (ok_sync) then
544     call histsync(nid_tra)
545     endif
546    
547     end subroutine write_histrac
548    
549     END SUBROUTINE phytrac
550    
551     !*************************************************
552    
553     subroutine ini_histrac(nid_tra, pdtphys, presnivs, nqmax, lessivage)
554    
555     ! From phylmd/ini_histrac.h, version 1.10 2006/02/21 08:08:30
556    
557     use dimens_m, only: iim, jjm, llm
558     use ioipsl, only: ymds2ju, histbeg_totreg, histvert, histdef, histend
559     use temps, only: annee_ref, day_ref, itau_phy
560     use advtrac_m, only: niadv, tnom, ttext
561     use dimphy, only: klon
562     use clesphys, only: ecrit_tra
563 guez 15 use grid_change, only: gr_phy_write_2d
564 guez 3 use phyetat0_m, only: rlon, rlat
565    
566     INTEGER, intent(out):: nid_tra
567     real, intent(in):: pdtphys ! pas d'integration pour la physique (s)
568     REAL, intent(in):: presnivs(:)
569    
570     integer, intent(in):: nqmax
571     ! (nombre de traceurs auxquels on applique la physique)
572    
573     logical, intent(in):: lessivage
574    
575     ! Variables local to the procedure:
576    
577     REAL zjulian
578     REAL zx_lat(iim, jjm+1)
579     INTEGER nhori, nvert
580     REAL zsto, zout
581     integer it, iq, iiq
582    
583     !---------------------------------------------------------
584    
585     CALL ymds2ju(annee_ref, month=1, day=day_ref, sec=0.0, julian=zjulian)
586 guez 15 zx_lat(:, :) = gr_phy_write_2d(rlat)
587     CALL histbeg_totreg("histrac", rlon(2:iim+1), zx_lat(1, :), &
588 guez 3 1, iim, 1, jjm+1, itau_phy, zjulian, pdtphys, nhori, nid_tra)
589     CALL histvert(nid_tra, "presnivs", "Vertical levels", "mb", llm, &
590     presnivs, nvert)
591    
592     zsto = pdtphys
593     zout = pdtphys * REAL(ecrit_tra)
594    
595     CALL histdef(nid_tra, "phis", "Surface geop. height", "-", &
596 guez 15 iim, jjm+1, nhori, 1, 1, 1, -99, &
597 guez 3 "once", zsto, zout)
598     CALL histdef(nid_tra, "aire", "Grid area", "-", &
599 guez 15 iim, jjm+1, nhori, 1, 1, 1, -99, &
600 guez 3 "once", zsto, zout)
601     CALL histdef(nid_tra, "zmasse", "column density of air in cell", &
602 guez 15 "kg m-2", iim, jjm + 1, nhori, llm, 1, llm, nvert, "ave(X)", &
603 guez 3 zsto, zout)
604    
605 guez 15 DO it = 1, nqmax
606 guez 3 ! champ 2D
607     iq=it+2
608     iiq=niadv(iq)
609     CALL histdef(nid_tra, tnom(iq), ttext(iiq), "U/kga", iim, jjm+1, &
610 guez 15 nhori, llm, 1, llm, nvert, "ave(X)", zsto, zout)
611 guez 3 if (lessivage) THEN
612     CALL histdef(nid_tra, "fl"//tnom(iq), "Flux "//ttext(iiq), &
613 guez 15 "U/m2/s", iim, jjm+1, nhori, llm, 1, llm, nvert, &
614 guez 3 "ave(X)", zsto, zout)
615     endif
616    
617     !---Ajout Olivia
618     CALL histdef(nid_tra, "d_tr_th_"//tnom(iq), &
619     "tendance thermique"// ttext(iiq), "?", &
620 guez 15 iim, jjm+1, nhori, llm, 1, llm, nvert, &
621 guez 3 "ave(X)", zsto, zout)
622     CALL histdef(nid_tra, "d_tr_cv_"//tnom(iq), &
623     "tendance convection"// ttext(iiq), "?", &
624 guez 15 iim, jjm+1, nhori, llm, 1, llm, nvert, &
625 guez 3 "ave(X)", zsto, zout)
626     CALL histdef(nid_tra, "d_tr_cl_"//tnom(iq), &
627     "tendance couche limite"// ttext(iiq), "?", &
628 guez 15 iim, jjm+1, nhori, llm, 1, llm, nvert, &
629 guez 3 "ave(X)", zsto, zout)
630     !---fin Olivia
631    
632     ENDDO
633    
634 guez 15 CALL histdef(nid_tra, "pplay", "", "-", &
635     iim, jjm+1, nhori, llm, 1, llm, nvert, &
636 guez 3 "inst(X)", zout, zout)
637 guez 15 CALL histdef(nid_tra, "t", "", "-", &
638     iim, jjm+1, nhori, llm, 1, llm, nvert, &
639 guez 3 "inst(X)", zout, zout)
640    
641     CALL histend(nid_tra)
642    
643     end subroutine ini_histrac
644    
645     !*************************************************
646    
647     function radiornpb(tr_seri, pdtphys, tautr)
648    
649     ! From phylmd/radiornpb.F, v 1.2 2005/05/25 13:10:09
650    
651     ! Auteurs: AA + CG (LGGE/CNRS) Date 24-06-94
652     ! Objet: Decroissance radioactive d'un traceur dans l'atmosphere
653     !G 24 06 94 : Pour un traceur, le radon
654     !G 16 12 94 : Plus un 2eme traceur, le 210Pb. Le radon decroit en plomb.
655    
656     ! Le pas de temps "pdtphys" est supposé beaucoup plus petit que la
657     ! constante de temps de décroissance.
658    
659     use dimens_m, only: llm
660     use dimphy, only: klon, nbtr
661 guez 13 use numer_rec, only: assert
662 guez 3
663     IMPLICIT none
664    
665     REAL, intent(in):: tr_seri(:, :, :), pdtphys, tautr(:)
666     real radiornpb(klon, llm, 2)
667    
668     ! Variable local to the procedure:
669     INTEGER it
670    
671     !-----------------------------------------------
672    
673     call assert(shape(tr_seri) == (/klon, llm, nbtr/), "radiornpb tr_seri")
674     call assert(size(tautr) == nbtr, "radiornpb tautr")
675    
676     DO it = 1, 2
677     IF (tautr(it) > 0.) THEN
678     radiornpb(:, :, it) = - tr_seri(:, :, it) * pdtphys / tautr(it)
679     ELSE
680     radiornpb(:, :, it) = 0.
681     END IF
682     END DO
683    
684     !G161294 : Cas particulier radon 1 => plomb 2
685     radiornpb(:, :, 2) = radiornpb(:, :, 2) - radiornpb(:, :, 1)
686    
687     END function radiornpb
688    
689     !*************************************************
690    
691     SUBROUTINE minmaxqfi(zq, qmin, qmax, comment)
692    
693     ! From phylmd/minmaxqfi.F, version 1.1.1.1 2004/05/19 12:53:09
694    
695     use dimens_m, only: llm
696     use dimphy, only: klon
697 guez 13 use numer_rec, only: assert
698 guez 3
699     IMPLICIT none
700    
701     real, intent(in):: zq(:, :), qmin, qmax
702     CHARACTER(len=*), intent(in):: comment
703    
704     ! Variables local to the procedure:
705    
706     INTEGER jadrs(klon), jbad, k, i
707    
708     !---------------------------------
709    
710     call assert(shape(zq) == (/klon, llm/), "minmaxqfi")
711    
712     DO k = 1, llm
713     jbad = 0
714     DO i = 1, klon
715     IF (zq(i, k) > qmax .OR. zq(i, k) < qmin) THEN
716     jbad = jbad + 1
717     jadrs(jbad) = i
718     ENDIF
719     ENDDO
720     IF (jbad > 0) THEN
721     PRINT *, comment
722     DO i = 1, jbad
723     PRINT *, "zq(", jadrs(i), ", ", k, ") = ", zq(jadrs(i), k)
724     ENDDO
725     ENDIF
726     ENDDO
727    
728     end SUBROUTINE minmaxqfi
729    
730     end module phytrac_m

  ViewVC Help
Powered by ViewVC 1.1.21