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

Annotation of /trunk/phylmd/phytrac.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 175 - (hide annotations)
Fri Feb 5 16:02:34 2016 UTC (8 years, 3 months ago) by guez
Original Path: trunk/Sources/phylmd/phytrac.f
File size: 15248 byte(s)
Added argument itau_phy to ini_histins, phyetat0, phytrac and
phyredem0. Removed variable itau_phy of module temps. Avoiding side
effect in etat0 and phyetat0. The procedures ini_histins, phyetat0,
phytrac and phyredem0 are all called by physiq so there is no
cascading variable penalty.

In procedure inifilr, made the condition on colat0 weaker to allow for
rounding error.

Removed arguments flux_o, flux_g and t_slab of clmain, flux_o and
flux_g of clqh and interfsurf_hq, tslab and seaice of phyetat0 and
phyredem. NetCDF variables TSLAB and SEAICE no longer in
restartphy.nc. All these variables were related to the not-implemented
slab ocean. seaice and tslab were just set to 0 in phyetat0 and never
used nor changed. flux_o and flux_g were computed in clmain but never
used in physiq.

Removed argument swnet of clqh. Was used only to compute a local
variable, swdown, which was not used.

1 guez 3 module phytrac_m
2    
3     IMPLICIT none
4    
5     private
6     public phytrac
7    
8     contains
9    
10 guez 98 SUBROUTINE phytrac(itap, lmt_pas, julien, gmtime, firstcal, lafin, pdtphys, &
11 guez 118 t_seri, paprs, pplay, pmfu, pmfd, pde_u, pen_d, coefh, fm_therm, &
12 guez 159 entr_therm, yu1, yv1, ftsol, pctsrf, frac_impa, frac_nucl, da, phi, &
13 guez 175 mp, upwd, dnwd, tr_seri, zmasse, ncid_startphy, nid_ins, itau_phy)
14 guez 3
15 guez 47 ! From phylmd/phytrac.F, version 1.15 2006/02/21 08:08:30 (SVN revision 679)
16 guez 3
17 guez 90 ! Authors: Fr\'ed\'eric Hourdin, Abderrahmane Idelkadi, Marie-Alice
18 guez 3 ! Foujols, Olivia
19 guez 78
20 guez 90 ! Objet : moniteur g\'en\'eral des tendances des traceurs
21 guez 3
22 guez 78 ! L'appel de "phytrac" se fait avec "nqmx - 2" donc nous avons
23 guez 98 ! bien les vrais traceurs, sans la vapeur d'eau ni l'eau liquide.
24 guez 3
25 guez 47 ! Modifications pour les traceurs :
26 guez 62 ! - uniformisation des parametrisations dans phytrac
27 guez 90 ! - stockage des moyennes des champs n\'ecessaires en mode traceur off-line
28 guez 47
29 guez 78 use abort_gcm_m, only: abort_gcm
30 guez 12 use clesphys, only: ecrit_tra
31     use clesphys2, only: iflag_con
32 guez 120 use cltrac_m, only: cltrac
33 guez 78 use cltracrn_m, only: cltracrn
34 guez 3 use ctherm, only: iflag_thermals
35 guez 120 use cvltr_m, only: cvltr
36 guez 98 use dimens_m, only: llm, nqmx
37     use dimphy, only: klon
38 guez 78 use indicesol, only: nbsrf
39 guez 98 use initrrnpb_m, only: initrrnpb
40 guez 17 use minmaxqfi_m, only: minmaxqfi
41 guez 171 use netcdf, only: NF90_FILL_float
42 guez 157 use netcdf95, only: nf95_inq_varid, nf95_get_var, nf95_put_var
43 guez 78 use nflxtr_m, only: nflxtr
44 guez 36 use nr_util, only: assert
45 guez 78 use o3_chem_m, only: o3_chem
46     use phyetat0_m, only: rlat
47 guez 157 use phyredem0_m, only: ncid_restartphy
48 guez 17 use press_coefoz_m, only: press_coefoz
49 guez 78 use radiornpb_m, only: radiornpb
50     use regr_pr_comb_coefoz_m, only: regr_pr_comb_coefoz
51     use SUPHEC_M, only: rg
52 guez 3
53 guez 78 integer, intent(in):: itap ! number of calls to "physiq"
54 guez 7 integer, intent(in):: lmt_pas ! number of time steps of "physics" per day
55 guez 3 integer, intent(in):: julien !jour julien, 1 <= julien <= 360
56 guez 90 real, intent(in):: gmtime ! heure de la journ\'ee en fraction de jour
57 guez 78 logical, intent(in):: firstcal ! first call to "calfis"
58     logical, intent(in):: lafin ! fin de la physique
59     real, intent(in):: pdtphys ! pas d'integration pour la physique (s)
60     real, intent(in):: t_seri(klon, llm) ! temperature, in K
61 guez 3
62     real, intent(in):: paprs(klon, llm+1)
63     ! (pression pour chaque inter-couche, en Pa)
64    
65 guez 10 real, intent(in):: pplay(klon, llm)
66     ! (pression pour le mileu de chaque couche, en Pa)
67    
68 guez 78 ! convection:
69 guez 3
70 guez 62 REAL, intent(in):: pmfu(klon, llm) ! flux de masse dans le panache montant
71 guez 72
72     REAL, intent(in):: pmfd(klon, llm)
73     ! flux de masse dans le panache descendant
74    
75 guez 78 REAL pde_u(klon, llm) ! flux detraine dans le panache montant
76     REAL pen_d(klon, llm) ! flux entraine dans le panache descendant
77     REAL coefh(klon, llm) ! coeff melange couche limite
78 guez 3
79 guez 78 ! thermiques:
80 guez 3 real fm_therm(klon, llm+1), entr_therm(klon, llm)
81    
82 guez 78 ! Couche limite:
83     REAL yu1(klon) ! vents au premier niveau
84     REAL yv1(klon) ! vents au premier niveau
85 guez 3
86 guez 90 ! Arguments n\'ecessaires pour les sources et puits de traceur :
87 guez 104 real, intent(in):: ftsol(klon, nbsrf) ! Temperature du sol (surf)(Kelvin)
88 guez 78 real pctsrf(klon, nbsrf) ! Pourcentage de sol f(nature du sol)
89 guez 3
90 guez 78 ! Lessivage pour le on-line
91     REAL frac_impa(klon, llm) ! fraction d'aerosols impactes
92     REAL frac_nucl(klon, llm) ! fraction d'aerosols nuclees
93 guez 3
94 guez 78 ! Kerry Emanuel
95 guez 99 real, intent(in):: da(klon, llm), phi(klon, llm, llm), mp(klon, llm)
96 guez 78 REAL, intent(in):: upwd(klon, llm) ! saturated updraft mass flux
97     REAL, intent(in):: dnwd(klon, llm) ! saturated downdraft mass flux
98 guez 3
99 guez 98 real, intent(inout):: tr_seri(:, :, :) ! (klon, llm, nqmx - 2)
100 guez 78 ! (mass fractions of tracers, excluding water, at mid-layers)
101 guez 3
102 guez 78 real, intent(in):: zmasse(:, :) ! (klon, llm)
103 guez 17 ! (column-density of mass of air in a cell, in kg m-2)
104 guez 3
105 guez 175 integer, intent(in):: ncid_startphy, nid_ins, itau_phy
106 guez 3
107 guez 157 ! Local:
108    
109 guez 17 integer nsplit
110    
111 guez 78 ! TRACEURS
112 guez 17
113 guez 3 ! Sources et puits des traceurs:
114    
115     ! Pour l'instant seuls les cas du rn et du pb ont ete envisages.
116    
117 guez 78 REAL source(klon) ! a voir lorsque le flux est prescrit
118 guez 3 !
119     ! Pour la source de radon et son reservoir de sol
120    
121 guez 156 REAL, save:: trs(klon, nqmx - 2) ! Concentration de traceur dans le sol
122 guez 3
123 guez 98 REAL masktr(klon, nqmx - 2) ! Masque reservoir de sol traceur
124 guez 78 ! Masque de l'echange avec la surface
125     ! (1 = reservoir) ou (possible => 1)
126 guez 3 SAVE masktr
127 guez 98 REAL fshtr(klon, nqmx - 2) ! Flux surfacique dans le reservoir de sol
128 guez 3 SAVE fshtr
129 guez 98 REAL hsoltr(nqmx - 2) ! Epaisseur equivalente du reservoir de sol
130 guez 3 SAVE hsoltr
131 guez 98 REAL tautr(nqmx - 2) ! Constante de decroissance radioactive
132 guez 3 SAVE tautr
133 guez 98 REAL vdeptr(nqmx - 2) ! Vitesse de depot sec dans la couche Brownienne
134 guez 3 SAVE vdeptr
135 guez 98 REAL scavtr(nqmx - 2) ! Coefficient de lessivage
136 guez 3 SAVE scavtr
137    
138     CHARACTER itn
139    
140     ! nature du traceur
141    
142 guez 98 logical aerosol(nqmx - 2) ! Nature du traceur
143 guez 78 ! ! aerosol(it) = true => aerosol
144     ! ! aerosol(it) = false => gaz
145 guez 98 logical clsol(nqmx - 2) ! couche limite sol calcul\'ee
146     logical radio(nqmx - 2) ! d\'ecroisssance radioactive
147 guez 3 save aerosol, clsol, radio
148    
149     ! convection tiedtke
150     INTEGER i, k, it
151     REAL delp(klon, llm)
152    
153     ! Variables liees a l'ecriture de la bande histoire physique
154    
155     ! Variables locales pour effectuer les appels en serie
156    
157     REAL d_tr(klon, llm), d_trs(klon) ! tendances de traceurs
158 guez 98 REAL d_tr_cl(klon, llm, nqmx - 2) ! tendance de traceurs couche limite
159 guez 156
160     REAL d_tr_cv(klon, llm, nqmx - 2)
161     ! tendance de traceurs conv pour chq traceur
162    
163 guez 98 REAL d_tr_th(klon, llm, nqmx - 2) ! la tendance des thermiques
164 guez 3 REAL d_tr_dec(klon, llm, 2) ! la tendance de la decroissance
165 guez 78 ! ! radioactive du rn - > pb
166 guez 98 REAL d_tr_lessi_impa(klon, llm, nqmx - 2) ! la tendance du lessivage
167 guez 78 ! ! par impaction
168 guez 98 REAL d_tr_lessi_nucl(klon, llm, nqmx - 2) ! la tendance du lessivage
169 guez 78 ! ! par nucleation
170 guez 98 REAL flestottr(klon, llm, nqmx - 2) ! flux de lessivage
171 guez 78 ! ! dans chaque couche
172 guez 3
173     real ztra_th(klon, llm)
174 guez 157 integer isplit, varid
175 guez 3
176     ! Controls:
177     logical:: couchelimite = .true.
178     logical:: convection = .true.
179     logical:: lessivage = .true.
180     logical, save:: inirnpb
181    
182     !--------------------------------------
183    
184 guez 18 call assert(shape(zmasse) == (/klon, llm/), "phytrac zmasse")
185 guez 98 call assert(shape(tr_seri) == (/klon, llm, nqmx - 2/), "phytrac tr_seri")
186 guez 3
187 guez 7 if (firstcal) then
188 guez 3 print *, 'phytrac: pdtphys = ', pdtphys
189 guez 91 PRINT *, 'Frequency of tracer output: ecrit_tra = ', ecrit_tra
190 guez 98 inirnpb = .true.
191 guez 3
192     ! Initialisation de certaines variables pour le radon et le plomb
193     ! Initialisation du traceur dans le sol (couche limite radonique)
194 guez 157 trs(:, 2:) = 0.
195 guez 3
196 guez 157 call nf95_inq_varid(ncid_startphy, "trs", varid)
197     call nf95_get_var(ncid_startphy, varid, trs(:, 1))
198 guez 171 if (any(trs(:, 1) == NF90_FILL_float)) call abort_gcm("phytrac", &
199     "some missing values in trs(:, 1)")
200 guez 3
201     ! Initialisation de la fraction d'aerosols lessivee
202    
203 guez 98 d_tr_lessi_impa = 0.
204     d_tr_lessi_nucl = 0.
205 guez 3
206     ! Initialisation de la nature des traceurs
207    
208 guez 98 DO it = 1, nqmx - 2
209 guez 78 aerosol(it) = .FALSE. ! Tous les traceurs sont des gaz par defaut
210 guez 90 radio(it) = .FALSE. ! par d\'efaut pas de passage par "radiornpb"
211 guez 78 clsol(it) = .FALSE. ! Par defaut couche limite avec flux prescrit
212 guez 3 ENDDO
213 guez 17
214 guez 98 if (nqmx >= 5) then
215 guez 17 call press_coefoz ! read input pressure levels for ozone coefficients
216     end if
217 guez 3 ENDIF
218    
219     if (inirnpb) THEN
220 guez 62 ! Initialisation du traceur dans le sol (couche limite radonique)
221 guez 3 radio(1)= .true.
222     radio(2)= .true.
223     clsol(1)= .true.
224     clsol(2)= .true.
225     aerosol(2) = .TRUE. ! le Pb est un aerosol
226 guez 98 call initrrnpb(pctsrf, masktr, fshtr, hsoltr, tautr, vdeptr, scavtr)
227 guez 3 inirnpb=.false.
228     endif
229    
230     if (convection) then
231 guez 62 ! Calcul de l'effet de la convection
232 guez 98 DO it=1, nqmx - 2
233 guez 62 if (iflag_con == 2) then
234     ! Tiedke
235 guez 78 CALL nflxtr(pdtphys, pmfu, pmfd, pde_u, pen_d, paprs, &
236     tr_seri(:, :, it), d_tr_cv(:, :, it))
237 guez 62 else if (iflag_con == 3) then
238     ! Emanuel
239 guez 120 call cvltr(pdtphys, da, phi, mp, paprs, tr_seri(:, :, it), upwd, &
240     dnwd, d_tr_cv(:, :, it))
241 guez 3 endif
242    
243     DO k = 1, llm
244     DO i = 1, klon
245     tr_seri(i, k, it) = tr_seri(i, k, it) + d_tr_cv(i, k, it)
246     ENDDO
247     ENDDO
248     WRITE(unit=itn, fmt='(i1)') it
249 guez 78 CALL minmaxqfi(tr_seri(:, :, it), 0., 1e33, &
250 guez 3 'convection, tracer index = ' // itn)
251     ENDDO
252     endif
253    
254     ! Calcul de l'effet des thermiques
255    
256 guez 98 do it=1, nqmx - 2
257 guez 3 do k=1, llm
258     do i=1, klon
259     d_tr_th(i, k, it)=0.
260     tr_seri(i, k, it)=max(tr_seri(i, k, it), 0.)
261 guez 78 tr_seri(i, k, it)=min(tr_seri(i, k, it), 1e10)
262 guez 3 enddo
263     enddo
264     enddo
265    
266     if (iflag_thermals > 0) then
267     nsplit=10
268 guez 98 DO it=1, nqmx - 2
269 guez 3 do isplit=1, nsplit
270     ! Thermiques
271     call dqthermcell(klon, llm, pdtphys/nsplit &
272     , fm_therm, entr_therm, zmasse &
273     , tr_seri(1:klon, 1:llm, it), d_tr, ztra_th)
274    
275     do k=1, llm
276     do i=1, klon
277     d_tr(i, k)=pdtphys*d_tr(i, k)/nsplit
278     d_tr_th(i, k, it)=d_tr_th(i, k, it)+d_tr(i, k)
279     tr_seri(i, k, it)=max(tr_seri(i, k, it)+d_tr(i, k), 0.)
280     enddo
281     enddo
282     enddo
283     ENDDO
284     endif
285    
286 guez 78 ! Calcul de l'effet de la couche limite
287 guez 3
288     if (couchelimite) then
289     DO k = 1, llm
290     DO i = 1, klon
291     delp(i, k) = paprs(i, k)-paprs(i, k+1)
292     ENDDO
293     ENDDO
294    
295 guez 98 ! MAF modif pour tenir compte du cas traceur
296     DO it=1, nqmx - 2
297 guez 3 if (clsol(it)) then
298     ! couche limite avec quantite dans le sol calculee
299 guez 156 CALL cltracrn(it, pdtphys, yu1, yv1, coefh, t_seri, ftsol, &
300     pctsrf, tr_seri(:, :, it), trs(:, it), paprs, pplay, delp, &
301     masktr(1, it), fshtr(1, it), hsoltr(it), tautr(it), &
302     vdeptr(it), rlat, d_tr_cl(1, 1, it), d_trs)
303 guez 3 DO k = 1, llm
304     DO i = 1, klon
305     tr_seri(i, k, it) = tr_seri(i, k, it) + d_tr_cl(i, k, it)
306     ENDDO
307     ENDDO
308    
309 guez 156 trs(:, it) = trs(:, it) + d_trs
310     else
311     ! couche limite avec flux prescrit
312 guez 3 !MAF provisoire source / traceur a creer
313     DO i=1, klon
314 guez 156 source(i) = 0. ! pas de source, pour l'instant
315 guez 3 ENDDO
316    
317 guez 120 CALL cltrac(pdtphys, coefh, t_seri, tr_seri(:, :, it), source, &
318     paprs, pplay, delp, d_tr_cl(1, 1, it))
319 guez 3 DO k = 1, llm
320     DO i = 1, klon
321     tr_seri(i, k, it) = tr_seri(i, k, it) + d_tr_cl(i, k, it)
322     ENDDO
323     ENDDO
324     endif
325     ENDDO
326 guez 98 endif
327 guez 3
328 guez 78 ! Calcul de l'effet du puits radioactif
329 guez 3
330     ! MAF il faudrait faire une modification pour passer dans radiornpb
331 guez 98 ! si radio=true
332     d_tr_dec = radiornpb(tr_seri, pdtphys, tautr)
333     DO it = 1, nqmx - 2
334     if (radio(it)) then
335     tr_seri(:, :, it) = tr_seri(:, :, it) + d_tr_dec(:, :, it)
336     WRITE(unit=itn, fmt='(i1)') it
337     CALL minmaxqfi(tr_seri(:, :, it), 0., 1e33, 'puits rn it='//itn)
338     endif
339     ENDDO
340 guez 3
341 guez 98 if (nqmx >= 5) then
342 guez 6 ! Ozone as a tracer:
343 guez 7 if (mod(itap - 1, lmt_pas) == 0) then
344     ! Once per day, update the coefficients for ozone chemistry:
345 guez 162 call regr_pr_comb_coefoz(julien, paprs, pplay)
346 guez 7 end if
347 guez 6 call o3_chem(julien, gmtime, t_seri, zmasse, pdtphys, tr_seri(:, :, 3))
348     end if
349 guez 3
350     ! Calcul de l'effet de la precipitation
351    
352     IF (lessivage) THEN
353 guez 98 d_tr_lessi_nucl = 0.
354     d_tr_lessi_impa = 0.
355     flestottr = 0.
356 guez 3
357     ! tendance des aerosols nuclees et impactes
358    
359 guez 98 DO it = 1, nqmx - 2
360 guez 3 IF (aerosol(it)) THEN
361     DO k = 1, llm
362     DO i = 1, klon
363     d_tr_lessi_nucl(i, k, it) = d_tr_lessi_nucl(i, k, it) + &
364 guez 78 (1 - frac_nucl(i, k))*tr_seri(i, k, it)
365 guez 3 d_tr_lessi_impa(i, k, it) = d_tr_lessi_impa(i, k, it) + &
366 guez 78 (1 - frac_impa(i, k))*tr_seri(i, k, it)
367 guez 3 ENDDO
368     ENDDO
369     ENDIF
370     ENDDO
371    
372     ! Mises a jour des traceurs + calcul des flux de lessivage
373     ! Mise a jour due a l'impaction et a la nucleation
374    
375 guez 98 DO it = 1, nqmx - 2
376 guez 3 IF (aerosol(it)) THEN
377     DO k = 1, llm
378     DO i = 1, klon
379 guez 78 tr_seri(i, k, it) = tr_seri(i, k, it) * frac_impa(i, k) &
380     * frac_nucl(i, k)
381 guez 3 ENDDO
382     ENDDO
383     ENDIF
384     ENDDO
385    
386     ! Flux lessivage total
387    
388 guez 98 DO it = 1, nqmx - 2
389 guez 3 DO k = 1, llm
390     DO i = 1, klon
391 guez 78 flestottr(i, k, it) = flestottr(i, k, it) &
392     - (d_tr_lessi_nucl(i, k, it) + d_tr_lessi_impa(i, k, it)) &
393     * (paprs(i, k)-paprs(i, k+1)) / (RG * pdtphys)
394 guez 3 ENDDO
395     ENDDO
396     ENDDO
397     ENDIF
398    
399 guez 78 ! Ecriture des sorties
400 guez 159 call write_histrac(lessivage, itap, nid_ins)
401 guez 3
402     if (lafin) then
403 guez 157 call nf95_inq_varid(ncid_restartphy, "trs", varid)
404     call nf95_put_var(ncid_restartphy, varid, trs(:, 1))
405 guez 3 endif
406    
407     contains
408    
409 guez 159 subroutine write_histrac(lessivage, itap, nid_ins)
410 guez 3
411     ! From phylmd/write_histrac.h, version 1.9 2006/02/21 08:08:30
412    
413     use dimens_m, only: iim, jjm, llm
414 guez 61 use histsync_m, only: histsync
415 guez 30 use histwrite_m, only: histwrite
416 guez 131 use iniadvtrac_m, only: tname
417 guez 3 use dimphy, only: klon
418 guez 32 use grid_change, only: gr_phy_write_2d
419     use gr_phy_write_3d_m, only: gr_phy_write_3d
420 guez 3
421     logical, intent(in):: lessivage
422 guez 78 integer, intent(in):: itap ! number of calls to "physiq"
423 guez 159 integer, intent(in):: nid_ins
424 guez 3
425     ! Variables local to the procedure:
426     integer it
427 guez 78 integer itau_w ! pas de temps ecriture
428 guez 3
429     !-----------------------------------------------------
430    
431 guez 7 itau_w = itau_phy + itap
432 guez 3
433 guez 159 CALL histwrite(nid_ins, "zmasse", itau_w, gr_phy_write_3d(zmasse))
434 guez 3
435 guez 98 DO it=1, nqmx - 2
436 guez 159 CALL histwrite(nid_ins, tname(it+2), itau_w, &
437 guez 20 gr_phy_write_3d(tr_seri(:, :, it)))
438 guez 3 if (lessivage) THEN
439 guez 159 CALL histwrite(nid_ins, "fl"//tname(it+2), itau_w, &
440 guez 20 gr_phy_write_3d(flestottr(:, :, it)))
441 guez 3 endif
442 guez 159 CALL histwrite(nid_ins, "d_tr_th_"//tname(it+2), itau_w, &
443 guez 20 gr_phy_write_3d(d_tr_th(:, :, it)))
444 guez 159 CALL histwrite(nid_ins, "d_tr_cv_"//tname(it+2), itau_w, &
445 guez 20 gr_phy_write_3d(d_tr_cv(:, :, it)))
446 guez 159 CALL histwrite(nid_ins, "d_tr_cl_"//tname(it+2), itau_w, &
447 guez 20 gr_phy_write_3d(d_tr_cl(:, :, it)))
448 guez 3 ENDDO
449    
450     end subroutine write_histrac
451    
452     END SUBROUTINE phytrac
453    
454     end module phytrac_m

  ViewVC Help
Powered by ViewVC 1.1.21