--- trunk/Sources/phylmd/phytrac.f 2016/03/15 17:51:30 181 +++ trunk/Sources/phylmd/phytrac.f 2017/10/16 12:35:41 225 @@ -7,15 +7,17 @@ contains - SUBROUTINE phytrac(itap, lmt_pas, julien, gmtime, firstcal, lafin, pdtphys, & - t_seri, paprs, pplay, pmfu, pmfd, pde_u, pen_d, coefh, fm_therm, & - entr_therm, yu1, yv1, ftsol, pctsrf, frac_impa, frac_nucl, da, phi, & - mp, upwd, dnwd, tr_seri, zmasse, ncid_startphy, nid_ins, itau_phy) - - ! From phylmd/phytrac.F, version 1.15 2006/02/21 08:08:30 (SVN revision 679) + SUBROUTINE phytrac(julien, gmtime, firstcal, lafin, pdtphys, t_seri, paprs, & + pplay, pmfu, pmfd, pde_u, pen_d, coefh, fm_therm, entr_therm, yu1, & + yv1, ftsol, pctsrf, frac_impa, frac_nucl, da, phi, mp, upwd, dnwd, & + tr_seri, zmasse, ncid_startphy) + + ! From phylmd/phytrac.F, version 1.15, 2006/02/21 08:08:30 (SVN + ! revision 679) and phylmd/write_histrac.h, version 1.9, + ! 2006/02/21 08:08:30 ! Authors: Fr\'ed\'eric Hourdin, Abderrahmane Idelkadi, Marie-Alice - ! Foujols, Olivia + ! Foujols ! Objet : moniteur g\'en\'eral des tendances des traceurs @@ -23,19 +25,21 @@ ! bien les vrais traceurs, sans la vapeur d'eau ni l'eau liquide. ! Modifications pour les traceurs : - ! - uniformisation des parametrisations dans phytrac + ! - uniformisation des param\'etrisations dans phytrac ! - stockage des moyennes des champs n\'ecessaires en mode traceur off-line use abort_gcm_m, only: abort_gcm - use clesphys, only: ecrit_tra - use clesphys2, only: iflag_con + use clesphys2, only: conv_emanuel use cltrac_m, only: cltrac use cltracrn_m, only: cltracrn + USE conf_gcm_m, ONLY: lmt_pas use ctherm, only: iflag_thermals use cvltr_m, only: cvltr use dimens_m, only: llm, nqmx use dimphy, only: klon + use histwrite_phy_m, only: histwrite_phy use indicesol, only: nbsrf + use iniadvtrac_m, only: tname use initrrnpb_m, only: initrrnpb use minmaxqfi_m, only: minmaxqfi use netcdf, only: NF90_FILL_float @@ -49,9 +53,8 @@ use radiornpb_m, only: radiornpb use regr_pr_comb_coefoz_m, only: regr_pr_comb_coefoz use SUPHEC_M, only: rg + use time_phylmdz, only: itap - integer, intent(in):: itap ! number of calls to "physiq" - integer, intent(in):: lmt_pas ! number of time steps of "physics" per day integer, intent(in):: julien !jour julien, 1 <= julien <= 360 real, intent(in):: gmtime ! heure de la journ\'ee en fraction de jour logical, intent(in):: firstcal ! first call to "calfis" @@ -75,21 +78,16 @@ REAL pde_u(klon, llm) ! flux detraine dans le panache montant REAL pen_d(klon, llm) ! flux entraine dans le panache descendant REAL coefh(klon, llm) ! coeff melange couche limite - - ! thermiques: - real fm_therm(klon, llm+1), entr_therm(klon, llm) - - ! Couche limite: - REAL yu1(klon) ! vents au premier niveau - REAL yv1(klon) ! vents au premier niveau + real fm_therm(klon, llm+1), entr_therm(klon, llm) ! thermiques + REAL, intent(in):: yu1(klon), yv1(klon) ! vent au premier niveau ! Arguments n\'ecessaires pour les sources et puits de traceur : - real, intent(in):: ftsol(klon, nbsrf) ! Temperature du sol (surf)(Kelvin) - real pctsrf(klon, nbsrf) ! Pourcentage de sol f(nature du sol) + real, intent(in):: ftsol(:, :) ! (klon, nbsrf) surface temperature (K) + real, intent(in):: pctsrf(klon, nbsrf) ! Pourcentage de sol f(nature du sol) ! Lessivage pour le on-line - REAL frac_impa(klon, llm) ! fraction d'aerosols impactes - REAL frac_nucl(klon, llm) ! fraction d'aerosols nuclees + REAL, intent(in):: frac_impa(klon, llm) ! fraction d'aerosols impactes + REAL, intent(in):: frac_nucl(klon, llm) ! fraction d'aerosols nuclees ! Kerry Emanuel real, intent(in):: da(klon, llm), phi(klon, llm, llm), mp(klon, llm) @@ -102,7 +100,7 @@ real, intent(in):: zmasse(:, :) ! (klon, llm) ! (column-density of mass of air in a cell, in kg m-2) - integer, intent(in):: ncid_startphy, nid_ins, itau_phy + integer, intent(in):: ncid_startphy ! Local: @@ -137,14 +135,13 @@ CHARACTER itn - ! nature du traceur - - logical aerosol(nqmx - 2) ! Nature du traceur + logical, save:: aerosol(nqmx - 2) ! Nature du traceur ! ! aerosol(it) = true => aerosol ! ! aerosol(it) = false => gaz - logical clsol(nqmx - 2) ! couche limite sol calcul\'ee - logical radio(nqmx - 2) ! d\'ecroisssance radioactive - save aerosol, clsol, radio + + logical, save:: clsol(nqmx - 2) ! couche limite sol flux + ! calcul\'ee, sinon prescrit + logical, save:: radio(nqmx - 2) ! d\'ecroisssance radioactive ! convection tiedtke INTEGER i, k, it @@ -163,21 +160,20 @@ REAL d_tr_th(klon, llm, nqmx - 2) ! la tendance des thermiques REAL d_tr_dec(klon, llm, 2) ! la tendance de la decroissance ! ! radioactive du rn - > pb - REAL d_tr_lessi_impa(klon, llm, nqmx - 2) ! la tendance du lessivage - ! ! par impaction - REAL d_tr_lessi_nucl(klon, llm, nqmx - 2) ! la tendance du lessivage - ! ! par nucleation - REAL flestottr(klon, llm, nqmx - 2) ! flux de lessivage - ! ! dans chaque couche + + REAL d_tr_lessi_impa(klon, llm, nqmx - 2) + ! tendance du lessivage par impaction + + REAL d_tr_lessi_nucl(klon, llm, nqmx - 2) + ! tendance du lessivage par nucleation + + REAL flestottr(klon, llm, nqmx - 2) ! flux de lessivage dans chaque couche real ztra_th(klon, llm) integer isplit, varid ! Controls: - logical:: couchelimite = .true. logical:: convection = .true. - logical:: lessivage = .true. - logical, save:: inirnpb !-------------------------------------- @@ -185,10 +181,6 @@ call assert(shape(tr_seri) == (/klon, llm, nqmx - 2/), "phytrac tr_seri") if (firstcal) then - print *, 'phytrac: pdtphys = ', pdtphys - PRINT *, 'Frequency of tracer output: ecrit_tra = ', ecrit_tra - inirnpb = .true. - ! Initialisation de certaines variables pour le radon et le plomb ! Initialisation du traceur dans le sol (couche limite radonique) trs(:, 2:) = 0. @@ -205,40 +197,31 @@ ! Initialisation de la nature des traceurs - DO it = 1, nqmx - 2 - aerosol(it) = .FALSE. ! Tous les traceurs sont des gaz par defaut - radio(it) = .FALSE. ! par d\'efaut pas de passage par "radiornpb" - clsol(it) = .FALSE. ! Par defaut couche limite avec flux prescrit - ENDDO + aerosol = .FALSE. ! Tous les traceurs sont des gaz par defaut + radio = .FALSE. ! par d\'efaut pas de passage par "radiornpb" if (nqmx >= 5) then call press_coefoz ! read input pressure levels for ozone coefficients end if - ENDIF - if (inirnpb) THEN ! Initialisation du traceur dans le sol (couche limite radonique) radio(1)= .true. radio(2)= .true. - clsol(1)= .true. - clsol(2)= .true. + clsol(:2)= .true. + clsol(3:)= .false. aerosol(2) = .TRUE. ! le Pb est un aerosol call initrrnpb(pctsrf, masktr, fshtr, hsoltr, tautr, vdeptr, scavtr) - inirnpb=.false. endif if (convection) then ! Calcul de l'effet de la convection DO it=1, nqmx - 2 - if (iflag_con == 2) then - ! Tiedke - CALL nflxtr(pdtphys, pmfu, pmfd, pde_u, pen_d, paprs, & - tr_seri(:, :, it), d_tr_cv(:, :, it)) - else - ! iflag_con >= 3 - ! Emanuel + if (conv_emanuel) then call cvltr(pdtphys, da, phi, mp, paprs, tr_seri(:, :, it), upwd, & dnwd, d_tr_cv(:, :, it)) + else + CALL nflxtr(pdtphys, pmfu, pmfd, pde_u, pen_d, paprs, & + tr_seri(:, :, it), d_tr_cv(:, :, it)) endif DO k = 1, llm @@ -286,45 +269,43 @@ ! Calcul de l'effet de la couche limite - if (couchelimite) then - DO k = 1, llm - DO i = 1, klon - delp(i, k) = paprs(i, k)-paprs(i, k+1) - ENDDO + DO k = 1, llm + DO i = 1, klon + delp(i, k) = paprs(i, k)-paprs(i, k+1) ENDDO + ENDDO - ! MAF modif pour tenir compte du cas traceur - DO it=1, nqmx - 2 - if (clsol(it)) then - ! couche limite avec quantite dans le sol calculee - CALL cltracrn(it, pdtphys, yu1, yv1, coefh, t_seri, ftsol, & - pctsrf, tr_seri(:, :, it), trs(:, it), paprs, pplay, delp, & - masktr(1, it), fshtr(1, it), hsoltr(it), tautr(it), & - vdeptr(it), rlat, d_tr_cl(1, 1, it), d_trs) - DO k = 1, llm - DO i = 1, klon - tr_seri(i, k, it) = tr_seri(i, k, it) + d_tr_cl(i, k, it) - ENDDO + ! MAF modif pour tenir compte du cas traceur + DO it=1, nqmx - 2 + if (clsol(it)) then + ! couche limite avec quantite dans le sol calculee + CALL cltracrn(it, pdtphys, yu1, yv1, coefh, t_seri, ftsol, & + pctsrf, tr_seri(:, :, it), trs(:, it), paprs, pplay, delp, & + masktr(1, it), fshtr(1, it), hsoltr(it), tautr(it), & + vdeptr(it), rlat, d_tr_cl(1, 1, it), d_trs) + DO k = 1, llm + DO i = 1, klon + tr_seri(i, k, it) = tr_seri(i, k, it) + d_tr_cl(i, k, it) ENDDO + ENDDO - trs(:, it) = trs(:, it) + d_trs - else - ! couche limite avec flux prescrit - !MAF provisoire source / traceur a creer - DO i=1, klon - source(i) = 0. ! pas de source, pour l'instant - ENDDO + trs(:, it) = trs(:, it) + d_trs + else + ! couche limite avec flux prescrit + !MAF provisoire source / traceur a creer + DO i=1, klon + source(i) = 0. ! pas de source, pour l'instant + ENDDO - CALL cltrac(pdtphys, coefh, t_seri, tr_seri(:, :, it), source, & - paprs, pplay, delp, d_tr_cl(1, 1, it)) - DO k = 1, llm - DO i = 1, klon - tr_seri(i, k, it) = tr_seri(i, k, it) + d_tr_cl(i, k, it) - ENDDO + CALL cltrac(pdtphys, coefh, t_seri, tr_seri(:, :, it), source, & + paprs, pplay, delp, d_tr_cl(1, 1, it)) + DO k = 1, llm + DO i = 1, klon + tr_seri(i, k, it) = tr_seri(i, k, it) + d_tr_cl(i, k, it) ENDDO - endif - ENDDO - endif + ENDDO + endif + ENDDO ! Calcul de l'effet du puits radioactif @@ -350,102 +331,65 @@ ! Calcul de l'effet de la precipitation - IF (lessivage) THEN - d_tr_lessi_nucl = 0. - d_tr_lessi_impa = 0. - flestottr = 0. + d_tr_lessi_nucl = 0. + d_tr_lessi_impa = 0. + flestottr = 0. - ! tendance des aerosols nuclees et impactes + ! tendance des aerosols nuclees et impactes - DO it = 1, nqmx - 2 - IF (aerosol(it)) THEN - DO k = 1, llm - DO i = 1, klon - d_tr_lessi_nucl(i, k, it) = d_tr_lessi_nucl(i, k, it) + & - (1 - frac_nucl(i, k))*tr_seri(i, k, it) - d_tr_lessi_impa(i, k, it) = d_tr_lessi_impa(i, k, it) + & - (1 - frac_impa(i, k))*tr_seri(i, k, it) - ENDDO - ENDDO - ENDIF - ENDDO - - ! Mises a jour des traceurs + calcul des flux de lessivage - ! Mise a jour due a l'impaction et a la nucleation - - DO it = 1, nqmx - 2 - IF (aerosol(it)) THEN - DO k = 1, llm - DO i = 1, klon - tr_seri(i, k, it) = tr_seri(i, k, it) * frac_impa(i, k) & - * frac_nucl(i, k) - ENDDO + DO it = 1, nqmx - 2 + IF (aerosol(it)) THEN + DO k = 1, llm + DO i = 1, klon + d_tr_lessi_nucl(i, k, it) = d_tr_lessi_nucl(i, k, it) + & + (1 - frac_nucl(i, k))*tr_seri(i, k, it) + d_tr_lessi_impa(i, k, it) = d_tr_lessi_impa(i, k, it) + & + (1 - frac_impa(i, k))*tr_seri(i, k, it) ENDDO - ENDIF - ENDDO + ENDDO + ENDIF + ENDDO - ! Flux lessivage total + ! Mises a jour des traceurs + calcul des flux de lessivage + ! Mise a jour due a l'impaction et a la nucleation - DO it = 1, nqmx - 2 + DO it = 1, nqmx - 2 + IF (aerosol(it)) THEN DO k = 1, llm DO i = 1, klon - flestottr(i, k, it) = flestottr(i, k, it) & - - (d_tr_lessi_nucl(i, k, it) + d_tr_lessi_impa(i, k, it)) & - * (paprs(i, k)-paprs(i, k+1)) / (RG * pdtphys) + tr_seri(i, k, it) = tr_seri(i, k, it) * frac_impa(i, k) & + * frac_nucl(i, k) ENDDO ENDDO + ENDIF + ENDDO + + ! Flux lessivage total + DO it = 1, nqmx - 2 + DO k = 1, llm + DO i = 1, klon + flestottr(i, k, it) = flestottr(i, k, it) & + - (d_tr_lessi_nucl(i, k, it) + d_tr_lessi_impa(i, k, it)) & + * (paprs(i, k)-paprs(i, k+1)) / (RG * pdtphys) + ENDDO ENDDO - ENDIF + ENDDO ! Ecriture des sorties - call write_histrac(lessivage, itap, nid_ins) + CALL histwrite_phy("zmasse", zmasse) + DO it=1, nqmx - 2 + CALL histwrite_phy(tname(it+2), tr_seri(:, :, it)) + CALL histwrite_phy("fl"//tname(it+2), flestottr(:, :, it)) + CALL histwrite_phy("d_tr_th_"//tname(it+2), d_tr_th(:, :, it)) + CALL histwrite_phy("d_tr_cv_"//tname(it+2), d_tr_cv(:, :, it)) + CALL histwrite_phy("d_tr_cl_"//tname(it+2), d_tr_cl(:, :, it)) + ENDDO if (lafin) then call nf95_inq_varid(ncid_restartphy, "trs", varid) call nf95_put_var(ncid_restartphy, varid, trs(:, 1)) endif - contains - - subroutine write_histrac(lessivage, itap, nid_ins) - - ! From phylmd/write_histrac.h, version 1.9 2006/02/21 08:08:30 - - use histwrite_m, only: histwrite - use iniadvtrac_m, only: tname - use gr_phy_write_3d_m, only: gr_phy_write_3d - - logical, intent(in):: lessivage - integer, intent(in):: itap ! number of calls to "physiq" - integer, intent(in):: nid_ins - - ! Variables local to the procedure: - integer it - integer itau_w ! pas de temps ecriture - - !----------------------------------------------------- - - itau_w = itau_phy + itap - - CALL histwrite(nid_ins, "zmasse", itau_w, gr_phy_write_3d(zmasse)) - - DO it=1, nqmx - 2 - CALL histwrite(nid_ins, tname(it+2), itau_w, & - gr_phy_write_3d(tr_seri(:, :, it))) - if (lessivage) THEN - CALL histwrite(nid_ins, "fl"//tname(it+2), itau_w, & - gr_phy_write_3d(flestottr(:, :, it))) - endif - CALL histwrite(nid_ins, "d_tr_th_"//tname(it+2), itau_w, & - gr_phy_write_3d(d_tr_th(:, :, it))) - CALL histwrite(nid_ins, "d_tr_cv_"//tname(it+2), itau_w, & - gr_phy_write_3d(d_tr_cv(:, :, it))) - CALL histwrite(nid_ins, "d_tr_cl_"//tname(it+2), itau_w, & - gr_phy_write_3d(d_tr_cl(:, :, it))) - ENDDO - - end subroutine write_histrac - END SUBROUTINE phytrac end module phytrac_m