--- trunk/libf/phylmd/phytrac.f90 2008/07/21 16:05:07 12 +++ trunk/libf/phylmd/phytrac.f90 2008/08/07 12:29:13 18 @@ -10,15 +10,16 @@ contains SUBROUTINE phytrac(rnpb, itap, lmt_pas, julien, gmtime, firstcal, lafin, & - nqmax, pdtphys, u, v, t_seri, paprs, pplay, pmfu, pmfd, pen_u, & + nq_phys, pdtphys, u, v, t_seri, paprs, pplay, pmfu, pmfd, pen_u, & pde_u, pen_d, pde_d, coefh, fm_therm, entr_therm, yu1, yv1, ftsol, & pctsrf, frac_impa, frac_nucl, presnivs, pphis, & pphi, albsol, rh, cldfra, rneb, diafra, cldliq, itop_con, & - ibas_con, pmflxr, pmflxs, prfl, psfl, da, phi, mp, upwd, dnwd, tr_seri) + ibas_con, pmflxr, pmflxs, prfl, psfl, da, phi, mp, upwd, dnwd, & + tr_seri, zmasse) ! From phylmd/phytrac.F, version 1.15 2006/02/21 08:08:30 - ! Authors : Frédéric Hourdin, Abderrahmane Idelkadi, Marie-Alice + ! Authors: Frédéric Hourdin, Abderrahmane Idelkadi, Marie-Alice ! Foujols, Olivia ! Objet : moniteur général des tendances des traceurs @@ -30,7 +31,7 @@ ! (peu propre). ! Pourrait-on avoir une variable qui indiquerait le type de traceur ? - use dimens_m, only: iim, jjm, llm + use dimens_m, only: llm use indicesol, only: nbsrf use dimphy, only: klon, nbtr use clesphys, only: ecrit_tra @@ -41,6 +42,11 @@ use regr_pr_comb_coefoz_m, only: regr_pr_comb_coefoz use phyetat0_m, only: rlat use o3_chem_m, only: o3_chem + use ini_hist, only: ini_histrac + use radiornpb_m, only: radiornpb + use minmaxqfi_m, only: minmaxqfi + use numer_rec, only: assert + use press_coefoz_m, only: press_coefoz ! Arguments: @@ -50,7 +56,7 @@ logical, intent(in):: rnpb - integer, intent(in):: nqmax + integer, intent(in):: nq_phys ! (nombre de traceurs auxquels on applique la physique) integer, intent(in):: itap ! number of calls to "physiq" @@ -62,7 +68,7 @@ real, intent(in):: pdtphys ! pas d'integration pour la physique (s) real, intent(in):: t_seri(klon, llm) ! temperature, in K - real tr_seri(klon, llm, nbtr) + real, intent(inout):: tr_seri(:, :, :) ! (klon, llm, nbtr) ! (mass fractions of tracers, excluding water, at mid-layers) real u(klon, llm) @@ -89,12 +95,10 @@ logical, intent(in):: firstcal ! first call to "calfis" logical, intent(in):: lafin ! fin de la physique - integer nsplit REAL pmflxr(klon, llm+1), pmflxs(klon, llm+1) !--lessivage convection REAL prfl(klon, llm+1), psfl(klon, llm+1) !--lessivage large-scale ! convection: - REAL pmfu(klon, llm) ! flux de masse dans le panache montant REAL pmfd(klon, llm) ! flux de masse dans le panache descendant REAL pen_u(klon, llm) ! flux entraine dans le panache montant @@ -129,10 +133,14 @@ real ftsol(klon, nbsrf) ! Temperature du sol (surf)(Kelvin) real pctsrf(klon, nbsrf) ! Pourcentage de sol f(nature du sol) - real pftsol1(klon), pftsol2(klon), pftsol3(klon), pftsol4(klon) - real ppsrf1(klon), ppsrf2(klon), ppsrf3(klon), ppsrf4(klon) + real, intent(in):: zmasse(:, :) ! (klon, llm) + ! (column-density of mass of air in a cell, in kg m-2) + + ! Variables local to the procedure: + + integer nsplit - ! VARIABLES LOCALES TRACEURS + ! TRACEURS ! Sources et puits des traceurs: @@ -192,13 +200,7 @@ REAL flestottr(klon, llm, nbtr) ! flux de lessivage ! ! dans chaque couche - real zmasse(klon, llm) - ! (column-density of mass of air in a layer, in kg m-2) - real ztra_th(klon, llm) - - character(len=20) modname - character(len=80) abort_message integer isplit ! Controls: @@ -209,19 +211,17 @@ !-------------------------------------- - modname='phytrac' + call assert(shape(zmasse) == (/klon, llm/), "phytrac zmasse") + call assert(shape(tr_seri) == (/klon, llm, nbtr/), "phytrac tr_seri") if (firstcal) then print *, 'phytrac: pdtphys = ', pdtphys PRINT *, 'Fréquence de sortie des traceurs : ecrit_tra = ', ecrit_tra - if (nbtr < nqmax) then - abort_message='See above' - call abort_gcm(modname, abort_message, 1) - endif + if (nbtr < nq_phys) call abort_gcm('phytrac', 'nbtr < nq_phys', 1) inirnpb=rnpb ! Initialisation des sorties : - call ini_histrac(nid_tra, pdtphys, presnivs, nqmax, lessivage) + call ini_histrac(nid_tra, pdtphys, presnivs, nq_phys, lessivage) ! Initialisation de certaines variables pour le radon et le plomb ! Initialisation du traceur dans le sol (couche limite radonique) @@ -240,11 +240,15 @@ ! Initialisation de la nature des traceurs - DO it = 1, nqmax + DO it = 1, nq_phys aerosol(it) = .FALSE. ! Tous les traceurs sont des gaz par defaut radio(it) = .FALSE. ! par défaut pas de passage par "radiornpb" clsol(it) = .FALSE. ! Par defaut couche limite avec flux prescrit ENDDO + + if (nq_phys >= 3) then + call press_coefoz ! read input pressure levels for ozone coefficients + end if ENDIF ! Initialisation du traceur dans le sol (couche limite radonique) @@ -261,23 +265,10 @@ inirnpb=.false. endif - do i=1, klon - pftsol1(i) = ftsol(i, 1) - pftsol2(i) = ftsol(i, 2) - pftsol3(i) = ftsol(i, 3) - pftsol4(i) = ftsol(i, 4) - - ppsrf1(i) = pctsrf(i, 1) - ppsrf2(i) = pctsrf(i, 2) - ppsrf3(i) = pctsrf(i, 3) - ppsrf4(i) = pctsrf(i, 4) - - enddo - ! Calcul de l'effet de la convection if (convection) then - DO it=1, nqmax + DO it=1, nq_phys if (iflag_con.eq.2) then ! tiedke CALL nflxtr(pdtphys, pmfu, pmfd, pen_u, pde_u, pen_d, pde_d, & @@ -299,11 +290,9 @@ ENDDO endif - forall (k=1: llm) zmasse(:, k) = (paprs(:, k)-paprs(:, k+1)) / rg - ! Calcul de l'effet des thermiques - do it=1, nqmax + do it=1, nq_phys do k=1, llm do i=1, klon d_tr_th(i, k, it)=0. @@ -315,7 +304,7 @@ if (iflag_thermals > 0) then nsplit=10 - DO it=1, nqmax + DO it=1, nq_phys do isplit=1, nsplit ! Thermiques call dqthermcell(klon, llm, pdtphys/nsplit & @@ -344,7 +333,7 @@ ENDDO ! MAF modif pour tenir compte du cas rnpb + traceur - DO it=1, nqmax + DO it=1, nq_phys if (clsol(it)) then ! couche limite avec quantite dans le sol calculee CALL cltracrn(it, pdtphys, yu1, yv1, & @@ -392,7 +381,7 @@ ! si radio=true mais pour l'instant radiornpb propre au cas rnpb if (rnpb) then d_tr_dec(:, :, :) = radiornpb(tr_seri, pdtphys, tautr) - DO it=1, nqmax + DO it=1, nq_phys if (radio(it)) then tr_seri(:, :, it) = tr_seri(:, :, it) + d_tr_dec(:, :, it) WRITE(unit=itn, fmt='(i1)') it @@ -401,7 +390,7 @@ ENDDO endif ! rnpb decroissance radioactive - if (nqmax >= 3) then + if (nq_phys >= 3) then ! Ozone as a tracer: if (mod(itap - 1, lmt_pas) == 0) then ! Once per day, update the coefficients for ozone chemistry: @@ -419,7 +408,7 @@ ! tendance des aerosols nuclees et impactes - DO it = 1, nqmax + DO it = 1, nq_phys IF (aerosol(it)) THEN DO k = 1, llm DO i = 1, klon @@ -435,7 +424,7 @@ ! Mises a jour des traceurs + calcul des flux de lessivage ! Mise a jour due a l'impaction et a la nucleation - DO it = 1, nqmax + DO it = 1, nq_phys IF (aerosol(it)) THEN DO k = 1, llm DO i = 1, klon @@ -448,7 +437,7 @@ ! Flux lessivage total - DO it = 1, nqmax + DO it = 1, nq_phys DO k = 1, llm DO i = 1, klon flestottr(i, k, it) = flestottr(i, k, it) - & @@ -462,7 +451,7 @@ ENDIF ! Ecriture des sorties - call write_histrac(lessivage, nqmax, itap, nid_tra) + call write_histrac(lessivage, nq_phys, itap, nid_tra) if (lafin) then print *, "C'est la fin de la physique." @@ -476,27 +465,26 @@ contains - subroutine write_histrac(lessivage, nqmax, itap, nid_tra) + subroutine write_histrac(lessivage, nq_phys, itap, nid_tra) ! From phylmd/write_histrac.h, version 1.9 2006/02/21 08:08:30 use dimens_m, only: iim, jjm, llm use ioipsl, only: histwrite, histsync use temps, only: itau_phy - use advtrac_m, only: tnom + use iniadvtrac_m, only: tnom use comgeomphy, only: airephy use dimphy, only: klon logical, intent(in):: lessivage - integer, intent(in):: nqmax + integer, intent(in):: nq_phys ! (nombre de traceurs auxquels on applique la physique) integer, intent(in):: itap ! number of calls to "physiq" integer, intent(in):: nid_tra ! Variables local to the procedure: - INTEGER ndex2d(iim*(jjm+1)), ndex3d(iim*(jjm+1)*llm) integer it integer itau_w ! pas de temps ecriture REAL zx_tmp_2d(iim, jjm+1), zx_tmp_3d(iim, jjm+1, llm) @@ -504,111 +492,39 @@ !----------------------------------------------------- - ndex2d = 0 - ndex3d = 0 itau_w = itau_phy + itap CALL gr_fi_ecrit(1, klon, iim, jjm+1, pphis, zx_tmp_2d) - CALL histwrite(nid_tra, "phis", itau_w, zx_tmp_2d, iim*(jjm+1), ndex2d) + CALL histwrite(nid_tra, "phis", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, jjm+1, airephy, zx_tmp_2d) - CALL histwrite(nid_tra, "aire", itau_w, zx_tmp_2d, iim*(jjm+1), ndex2d) + CALL histwrite(nid_tra, "aire", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(llm, klon, iim, jjm+1, zmasse, zx_tmp_3d) - CALL histwrite(nid_tra, "zmasse", itau_w, zx_tmp_3d, iim*(jjm+1)*llm, & - ndex3d) + CALL histwrite(nid_tra, "zmasse", itau_w, zx_tmp_3d) - DO it=1, nqmax + DO it=1, nq_phys CALL gr_fi_ecrit(llm, klon, iim, jjm+1, tr_seri(1, 1, it), zx_tmp_3d) - CALL histwrite(nid_tra, tnom(it+2), itau_w, zx_tmp_3d, & - iim*(jjm+1)*llm, ndex3d) + CALL histwrite(nid_tra, tnom(it+2), itau_w, zx_tmp_3d) if (lessivage) THEN CALL gr_fi_ecrit(llm, klon, iim, jjm+1, flestottr(1, 1, it), & zx_tmp_3d) - CALL histwrite(nid_tra, "fl"//tnom(it+2), itau_w, zx_tmp_3d, & - iim*(jjm+1)*llm, ndex3d) + CALL histwrite(nid_tra, "fl"//tnom(it+2), itau_w, zx_tmp_3d) endif CALL gr_fi_ecrit(llm, klon, iim, jjm+1, d_tr_th(1, 1, it), zx_tmp_3d) - CALL histwrite(nid_tra, "d_tr_th_"//tnom(it+2), itau_w, zx_tmp_3d, & - iim*(jjm+1)*llm, ndex3d) + CALL histwrite(nid_tra, "d_tr_th_"//tnom(it+2), itau_w, zx_tmp_3d) CALL gr_fi_ecrit(llm, klon, iim, jjm+1, d_tr_cv(1, 1, it), zx_tmp_3d) - CALL histwrite(nid_tra, "d_tr_cv_"//tnom(it+2), itau_w, zx_tmp_3d, & - iim*(jjm+1)*llm, ndex3d) + CALL histwrite(nid_tra, "d_tr_cv_"//tnom(it+2), itau_w, zx_tmp_3d) CALL gr_fi_ecrit(llm, klon, iim, jjm+1, d_tr_cl(1, 1, it), zx_tmp_3d) - CALL histwrite(nid_tra, "d_tr_cl_"//tnom(it+2), itau_w, zx_tmp_3d, & - iim*(jjm+1)*llm, ndex3d) + CALL histwrite(nid_tra, "d_tr_cl_"//tnom(it+2), itau_w, zx_tmp_3d) ENDDO - CALL gr_fi_ecrit(1, klon, iim, jjm+1, yu1, zx_tmp_2d) - CALL histwrite(nid_tra, "pyu1", itau_w, zx_tmp_2d, & - iim*(jjm+1), ndex2d) - - CALL gr_fi_ecrit(1, klon, iim, jjm+1, yv1, zx_tmp_2d) - CALL histwrite(nid_tra, "pyv1", itau_w, zx_tmp_2d, & - iim*(jjm+1), ndex2d) - - CALL gr_fi_ecrit(1, klon, iim, jjm+1, pftsol1, zx_tmp_2d) - CALL histwrite(nid_tra, "ftsol1", itau_w, zx_tmp_2d, & - iim*(jjm+1), ndex2d) - - CALL gr_fi_ecrit(1, klon, iim, jjm+1, pftsol2, zx_tmp_2d) - CALL histwrite(nid_tra, "ftsol2", itau_w, zx_tmp_2d, & - iim*(jjm+1), ndex2d) - - CALL gr_fi_ecrit(1, klon, iim, jjm+1, pftsol3, zx_tmp_2d) - CALL histwrite(nid_tra, "ftsol3", itau_w, zx_tmp_2d, & - iim*(jjm+1), ndex2d) - - CALL gr_fi_ecrit(1, klon, iim, jjm+1, pftsol4, zx_tmp_2d) - CALL histwrite(nid_tra, "ftsol4", itau_w, zx_tmp_2d, & - iim*(jjm+1), ndex2d) - - CALL gr_fi_ecrit(1, klon, iim, jjm+1, ppsrf1, zx_tmp_2d) - CALL histwrite(nid_tra, "psrf1", itau_w, zx_tmp_2d, & - iim*(jjm+1), ndex2d) - - CALL gr_fi_ecrit(1, klon, iim, jjm+1, ppsrf2, zx_tmp_2d) - CALL histwrite(nid_tra, "psrf2", itau_w, zx_tmp_2d, & - iim*(jjm+1), ndex2d) - - CALL gr_fi_ecrit(1, klon, iim, jjm+1, ppsrf3, zx_tmp_2d) - CALL histwrite(nid_tra, "psrf3", itau_w, zx_tmp_2d, & - iim*(jjm+1), ndex2d) - - CALL gr_fi_ecrit(1, klon, iim, jjm+1, ppsrf4, zx_tmp_2d) - CALL histwrite(nid_tra, "psrf4", itau_w, zx_tmp_2d, & - iim*(jjm+1), ndex2d) CALL gr_fi_ecrit(llm, klon, iim, jjm+1, pplay, zx_tmp_3d) - CALL histwrite(nid_tra, "pplay", itau_w, zx_tmp_3d, & - iim*(jjm+1)*llm, ndex3d) + CALL histwrite(nid_tra, "pplay", itau_w, zx_tmp_3d) CALL gr_fi_ecrit(llm, klon, iim, jjm+1, t_seri, zx_tmp_3d) - CALL histwrite(nid_tra, "t", itau_w, zx_tmp_3d, & - iim*(jjm+1)*llm, ndex3d) - CALL gr_fi_ecrit(llm, klon, iim, jjm+1, pmfu, zx_tmp_3d) - CALL histwrite(nid_tra, "mfu", itau_w, zx_tmp_3d, & - iim*(jjm+1)*llm, ndex3d) - CALL gr_fi_ecrit(llm, klon, iim, jjm+1, pmfd, zx_tmp_3d) - CALL histwrite(nid_tra, "mfd", itau_w, zx_tmp_3d, & - iim*(jjm+1)*llm, ndex3d) - CALL gr_fi_ecrit(llm, klon, iim, jjm+1, pen_u, zx_tmp_3d) - CALL histwrite(nid_tra, "en_u", itau_w, zx_tmp_3d, & - iim*(jjm+1)*llm, ndex3d) - CALL gr_fi_ecrit(llm, klon, iim, jjm+1, pen_d, zx_tmp_3d) - CALL histwrite(nid_tra, "en_d", itau_w, zx_tmp_3d, & - iim*(jjm+1)*llm, ndex3d) - CALL gr_fi_ecrit(llm, klon, iim, jjm+1, pde_d, zx_tmp_3d) - CALL histwrite(nid_tra, "de_d", itau_w, zx_tmp_3d, & - iim*(jjm+1)*llm, ndex3d) - CALL gr_fi_ecrit(llm, klon, iim, jjm+1, pde_u, zx_tmp_3d) - CALL histwrite(nid_tra, "de_u", itau_w, zx_tmp_3d, & - iim*(jjm+1)*llm, ndex3d) - CALL gr_fi_ecrit(llm, klon, iim, jjm+1, coefh, zx_tmp_3d) - CALL histwrite(nid_tra, "coefh", itau_w, zx_tmp_3d, & - iim*(jjm+1)*llm, ndex3d) - - ! abder + CALL histwrite(nid_tra, "t", itau_w, zx_tmp_3d) if (ok_sync) then call histsync(nid_tra) @@ -618,235 +534,4 @@ END SUBROUTINE phytrac - !************************************************* - - subroutine ini_histrac(nid_tra, pdtphys, presnivs, nqmax, lessivage) - - ! From phylmd/ini_histrac.h, version 1.10 2006/02/21 08:08:30 - - use dimens_m, only: iim, jjm, llm - use ioipsl, only: ymds2ju, histbeg_totreg, histvert, histdef, histend - use temps, only: annee_ref, day_ref, itau_phy - use advtrac_m, only: niadv, tnom, ttext - use dimphy, only: klon - use clesphys, only: ecrit_tra - use grid_change, only: gr_phy_write - use phyetat0_m, only: rlon, rlat - - INTEGER, intent(out):: nid_tra - real, intent(in):: pdtphys ! pas d'integration pour la physique (s) - REAL, intent(in):: presnivs(:) - - integer, intent(in):: nqmax - ! (nombre de traceurs auxquels on applique la physique) - - logical, intent(in):: lessivage - - ! Variables local to the procedure: - - REAL zjulian - REAL zx_lat(iim, jjm+1) - INTEGER nhori, nvert - REAL zsto, zout - integer it, iq, iiq - - !--------------------------------------------------------- - - CALL ymds2ju(annee_ref, month=1, day=day_ref, sec=0.0, julian=zjulian) - zx_lat(:, :) = gr_phy_write(rlat) - CALL histbeg_totreg("histrac", iim, rlon(2:iim+1), jjm+1, zx_lat(1, :), & - 1, iim, 1, jjm+1, itau_phy, zjulian, pdtphys, nhori, nid_tra) - CALL histvert(nid_tra, "presnivs", "Vertical levels", "mb", llm, & - presnivs, nvert) - - zsto = pdtphys - zout = pdtphys * REAL(ecrit_tra) - - CALL histdef(nid_tra, "phis", "Surface geop. height", "-", & - iim, jjm+1, nhori, 1, 1, 1, -99, 32, & - "once", zsto, zout) - CALL histdef(nid_tra, "aire", "Grid area", "-", & - iim, jjm+1, nhori, 1, 1, 1, -99, 32, & - "once", zsto, zout) - CALL histdef(nid_tra, "zmasse", "column density of air in cell", & - "kg m-2", iim, jjm + 1, nhori, llm, 1, llm, nvert, 32, "ave(X)", & - zsto, zout) - - DO it=1, nqmax - ! champ 2D - iq=it+2 - iiq=niadv(iq) - CALL histdef(nid_tra, tnom(iq), ttext(iiq), "U/kga", iim, jjm+1, & - nhori, llm, 1, llm, nvert, 32, "ave(X)", zsto, zout) - if (lessivage) THEN - CALL histdef(nid_tra, "fl"//tnom(iq), "Flux "//ttext(iiq), & - "U/m2/s", iim, jjm+1, nhori, llm, 1, llm, nvert, 32, & - "ave(X)", zsto, zout) - endif - - !---Ajout Olivia - CALL histdef(nid_tra, "d_tr_th_"//tnom(iq), & - "tendance thermique"// ttext(iiq), "?", & - iim, jjm+1, nhori, llm, 1, llm, nvert, 32, & - "ave(X)", zsto, zout) - CALL histdef(nid_tra, "d_tr_cv_"//tnom(iq), & - "tendance convection"// ttext(iiq), "?", & - iim, jjm+1, nhori, llm, 1, llm, nvert, 32, & - "ave(X)", zsto, zout) - CALL histdef(nid_tra, "d_tr_cl_"//tnom(iq), & - "tendance couche limite"// ttext(iiq), "?", & - iim, jjm+1, nhori, llm, 1, llm, nvert, 32, & - "ave(X)", zsto, zout) - !---fin Olivia - - ENDDO - - CALL histdef(nid_tra, "pyu1", "Vent niv 1", "-", & - iim, jjm+1, nhori, 1, 1, 1, -99, 32, & - "inst(X)", zout, zout) - - CALL histdef(nid_tra, "pyv1", "Vent niv 1", "-", & - iim, jjm+1, nhori, 1, 1, 1, -99, 32, & - "inst(X)", zout, zout) - CALL histdef(nid_tra, "psrf1", "nature sol", "-", & - iim, jjm+1, nhori, 1, 1, 1, -99, 32, & - "inst(X)", zout, zout) - CALL histdef(nid_tra, "psrf2", "nature sol", "-", & - iim, jjm+1, nhori, 1, 1, 1, -99, 32, & - "inst(X)", zout, zout) - CALL histdef(nid_tra, "psrf3", "nature sol", "-", & - iim, jjm+1, nhori, 1, 1, 1, -99, 32, & - "inst(X)", zout, zout) - CALL histdef(nid_tra, "psrf4", "nature sol", "-", & - iim, jjm+1, nhori, 1, 1, 1, -99, 32, & - "inst(X)", zout, zout) - CALL histdef(nid_tra, "ftsol1", "temper sol", "-", & - iim, jjm+1, nhori, 1, 1, 1, -99, 32, & - "inst(X)", zout, zout) - CALL histdef(nid_tra, "ftsol2", "temper sol", "-", & - iim, jjm+1, nhori, 1, 1, 1, -99, 32, & - "inst(X)", zout, zout) - CALL histdef(nid_tra, "ftsol3", "temper sol", "-", & - iim, jjm+1, nhori, 1, 1, 1, -99, 32, & - "inst(X)", zout, zout) - CALL histdef(nid_tra, "ftsol4", "temper sol", "-", & - iim, jjm+1, nhori, 1, 1, 1, -99, 32, & - "inst(X)", zout, zout) - CALL histdef(nid_tra, "pplay", "flux u mont", "-", & - iim, jjm+1, nhori, llm, 1, llm, nvert, 32, & - "inst(X)", zout, zout) - CALL histdef(nid_tra, "t", "flux u mont", "-", & - iim, jjm+1, nhori, llm, 1, llm, nvert, 32, & - "inst(X)", zout, zout) - CALL histdef(nid_tra, "mfu", "flux u mont", "-", & - iim, jjm+1, nhori, llm, 1, llm, nvert, 32, & - "ave(X)", zsto, zout) - CALL histdef(nid_tra, "mfd", "flux u decen", "-", & - iim, jjm+1, nhori, llm, 1, llm, nvert, 32, & - "ave(X)", zsto, zout) - CALL histdef(nid_tra, "en_u", "flux u mont", "-", & - iim, jjm+1, nhori, llm, 1, llm, nvert, 32, & - "ave(X)", zsto, zout) - CALL histdef(nid_tra, "en_d", "flux u mont", "-", & - iim, jjm+1, nhori, llm, 1, llm, nvert, 32, & - "ave(X)", zsto, zout) - CALL histdef(nid_tra, "de_d", "flux u mont", "-", & - iim, jjm+1, nhori, llm, 1, llm, nvert, 32, & - "ave(X)", zsto, zout) - CALL histdef(nid_tra, "de_u", "flux u decen", "-", & - iim, jjm+1, nhori, llm, 1, llm, nvert, 32, & - "ave(X)", zsto, zout) - CALL histdef(nid_tra, "coefh", "turbulent coef", "-", & - iim, jjm+1, nhori, llm, 1, llm, nvert, 32, & - "ave(X)", zsto, zout) - - CALL histend(nid_tra) - - end subroutine ini_histrac - - !************************************************* - - function radiornpb(tr_seri, pdtphys, tautr) - - ! From phylmd/radiornpb.F, v 1.2 2005/05/25 13:10:09 - - ! Auteurs: AA + CG (LGGE/CNRS) Date 24-06-94 - ! Objet: Decroissance radioactive d'un traceur dans l'atmosphere - !G 24 06 94 : Pour un traceur, le radon - !G 16 12 94 : Plus un 2eme traceur, le 210Pb. Le radon decroit en plomb. - - ! Le pas de temps "pdtphys" est supposé beaucoup plus petit que la - ! constante de temps de décroissance. - - use dimens_m, only: llm - use dimphy, only: klon, nbtr - use nrutil, only: assert - - IMPLICIT none - - REAL, intent(in):: tr_seri(:, :, :), pdtphys, tautr(:) - real radiornpb(klon, llm, 2) - - ! Variable local to the procedure: - INTEGER it - - !----------------------------------------------- - - call assert(shape(tr_seri) == (/klon, llm, nbtr/), "radiornpb tr_seri") - call assert(size(tautr) == nbtr, "radiornpb tautr") - - DO it = 1, 2 - IF (tautr(it) > 0.) THEN - radiornpb(:, :, it) = - tr_seri(:, :, it) * pdtphys / tautr(it) - ELSE - radiornpb(:, :, it) = 0. - END IF - END DO - - !G161294 : Cas particulier radon 1 => plomb 2 - radiornpb(:, :, 2) = radiornpb(:, :, 2) - radiornpb(:, :, 1) - - END function radiornpb - - !************************************************* - - SUBROUTINE minmaxqfi(zq, qmin, qmax, comment) - - ! From phylmd/minmaxqfi.F, version 1.1.1.1 2004/05/19 12:53:09 - - use dimens_m, only: llm - use dimphy, only: klon - use nrutil, only: assert - - IMPLICIT none - - real, intent(in):: zq(:, :), qmin, qmax - CHARACTER(len=*), intent(in):: comment - - ! Variables local to the procedure: - - INTEGER jadrs(klon), jbad, k, i - - !--------------------------------- - - call assert(shape(zq) == (/klon, llm/), "minmaxqfi") - - DO k = 1, llm - jbad = 0 - DO i = 1, klon - IF (zq(i, k) > qmax .OR. zq(i, k) < qmin) THEN - jbad = jbad + 1 - jadrs(jbad) = i - ENDIF - ENDDO - IF (jbad > 0) THEN - PRINT *, comment - DO i = 1, jbad - PRINT *, "zq(", jadrs(i), ", ", k, ") = ", zq(jadrs(i), k) - ENDDO - ENDIF - ENDDO - - end SUBROUTINE minmaxqfi - end module phytrac_m