--- trunk/libf/phylmd/phytrac.f90 2008/08/05 13:31:32 17 +++ trunk/libf/phylmd/phytrac.f90 2012/07/26 14:37:37 62 @@ -1,7 +1,5 @@ module phytrac_m - ! This module is clean: no C preprocessor directive, no include line. - IMPLICIT none private @@ -10,26 +8,24 @@ contains SUBROUTINE phytrac(rnpb, itap, lmt_pas, julien, gmtime, firstcal, lafin, & - nqmax, 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, zmasse) + nq_phys, pdtphys, u, 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, pphis, albsol, rh, cldfra, rneb, diafra, cldliq, & + 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 + ! From phylmd/phytrac.F, version 1.15 2006/02/21 08:08:30 (SVN revision 679) - ! 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 - ! Remarques : - ! 1/ L'appel de "phytrac" se fait avec "nq-2" donc nous avons bien + ! L'appel de "phytrac" se fait avec "nqmx-2" donc nous avons bien ! les vrais traceurs (en nombre "nbtr", sans la vapeur d'eau ni l'eau ! liquide) dans "phytrac". - ! 2/ Le choix du radon et du plomb se fait juste avec un "data" - ! (peu propre). - ! Pourrait-on avoir une variable qui indiquerait le type de traceur ? + + ! Modifications pour les traceurs : + ! - uniformisation des parametrisations dans phytrac + ! - stockage des moyennes des champs nécessaires en mode traceur off-line use dimens_m, only: llm use indicesol, only: nbsrf @@ -37,42 +33,33 @@ use clesphys, only: ecrit_tra use clesphys2, only: iflag_con use abort_gcm_m, only: abort_gcm - use YOMCST, only: rg + use SUPHEC_M, only: rg use ctherm, only: iflag_thermals 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 ini_histrac_m, only: ini_histrac use radiornpb_m, only: radiornpb use minmaxqfi_m, only: minmaxqfi - use numer_rec, only: assert + use nr_util, only: assert use press_coefoz_m, only: press_coefoz - ! Arguments: - - ! EN ENTREE: - - ! divers: - 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" integer, intent(in):: lmt_pas ! number of time steps of "physics" per day integer, intent(in):: julien !jour julien, 1 <= julien <= 360 - integer itop_con(klon) - integer ibas_con(klon) real, intent(in):: gmtime ! heure de la journée en fraction de jour real, intent(in):: pdtphys ! pas d'integration pour la physique (s) real, intent(in):: t_seri(klon, llm) ! temperature, in K - real, intent(inout):: 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) - real v(klon, llm) + real, intent(in):: u(klon, llm) real rh(klon, llm) ! humidite relative real cldliq(klon, llm) ! eau liquide nuageuse real cldfra(klon, llm) ! fraction nuageuse (tous les nuages) @@ -89,9 +76,7 @@ real, intent(in):: pplay(klon, llm) ! (pression pour le mileu de chaque couche, en Pa) - real pphi(klon, llm) ! geopotentiel - real pphis(klon) - REAL, intent(in):: presnivs(llm) + real, intent(in):: pphis(klon) logical, intent(in):: firstcal ! first call to "calfis" logical, intent(in):: lafin ! fin de la physique @@ -99,7 +84,7 @@ 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, intent(in):: 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 @@ -110,10 +95,10 @@ REAL pde_u(klon, llm) ! flux detraine dans le panache montant REAL pen_d(klon, llm) ! flux entraine dans le panache descendant REAL pde_d(klon, llm) ! flux detraine dans le panache descendant - ! KE + ! Kerry Emanuel real da(klon, llm), phi(klon, llm, llm), mp(klon, llm) - REAL upwd(klon, llm) ! saturated updraft mass flux - REAL dnwd(klon, llm) ! saturated downdraft mass flux + REAL, intent(in):: upwd(klon, llm) ! saturated updraft mass flux + REAL, intent(in):: dnwd(klon, llm) ! saturated downdraft mass flux ! Couche limite: @@ -211,16 +196,17 @@ !-------------------------------------- - call assert(shape(zmasse) == (/klon, llm/), "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) call abort_gcm('phytrac', 'See above', 1) + 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, nq_phys, lessivage) ! Initialisation de certaines variables pour le radon et le plomb ! Initialisation du traceur dans le sol (couche limite radonique) @@ -239,43 +225,40 @@ ! 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 (nqmax >= 3) then + 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) if (inirnpb) THEN - + ! Initialisation du traceur dans le sol (couche limite radonique) radio(1)= .true. radio(2)= .true. clsol(1)= .true. clsol(2)= .true. aerosol(2) = .TRUE. ! le Pb est un aerosol - call initrrnpb(ftsol, pctsrf, masktr, fshtr, hsoltr, tautr, vdeptr, & scavtr) inirnpb=.false. endif - ! Calcul de l'effet de la convection - if (convection) then - DO it=1, nqmax - if (iflag_con.eq.2) then - ! tiedke + ! Calcul de l'effet de la convection + DO it=1, nq_phys + if (iflag_con == 2) then + ! Tiedke CALL nflxtr(pdtphys, pmfu, pmfd, pen_u, pde_u, pen_d, pde_d, & paprs, tr_seri(1, 1, it), d_tr_cv(1, 1, it)) - else if (iflag_con.eq.3) then - ! KE - call cvltr(pdtphys, da, phi, mp, paprs, & - tr_seri(1, 1, it), upwd, dnwd, d_tr_cv(1, 1, it)) + else if (iflag_con == 3) then + ! Emanuel + call cvltr(pdtphys, da, phi, mp, paprs, tr_seri(1, 1, it), upwd, & + dnwd, d_tr_cv(1, 1, it)) endif DO k = 1, llm @@ -291,7 +274,7 @@ ! 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. @@ -303,7 +286,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 & @@ -332,7 +315,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, & @@ -380,7 +363,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 @@ -389,7 +372,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: @@ -407,7 +390,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 @@ -423,7 +406,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 @@ -436,7 +419,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) - & @@ -450,7 +433,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." @@ -464,20 +447,23 @@ 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 histsync_m, only: histsync + use histwrite_m, only: histwrite use temps, only: itau_phy - use advtrac_m, only: tnom + use iniadvtrac_m, only: tnom use comgeomphy, only: airephy use dimphy, only: klon + use grid_change, only: gr_phy_write_2d + use gr_phy_write_3d_m, only: gr_phy_write_3d 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" @@ -486,44 +472,33 @@ ! Variables local to the procedure: integer it integer itau_w ! pas de temps ecriture - REAL zx_tmp_2d(iim, jjm+1), zx_tmp_3d(iim, jjm+1, llm) logical, parameter:: ok_sync = .true. !----------------------------------------------------- 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) - - CALL gr_fi_ecrit(1, klon, iim, jjm+1, airephy, zx_tmp_2d) - 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) - - DO it=1, nqmax - 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) + CALL histwrite(nid_tra, "phis", itau_w, gr_phy_write_2d(pphis)) + CALL histwrite(nid_tra, "aire", itau_w, gr_phy_write_2d(airephy)) + CALL histwrite(nid_tra, "zmasse", itau_w, gr_phy_write_3d(zmasse)) + + DO it=1, nq_phys + CALL histwrite(nid_tra, tnom(it+2), itau_w, & + gr_phy_write_3d(tr_seri(:, :, it))) 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) + CALL histwrite(nid_tra, "fl"//tnom(it+2), itau_w, & + gr_phy_write_3d(flestottr(:, :, it))) 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) - 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) - 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) + CALL histwrite(nid_tra, "d_tr_th_"//tnom(it+2), itau_w, & + gr_phy_write_3d(d_tr_th(:, :, it))) + CALL histwrite(nid_tra, "d_tr_cv_"//tnom(it+2), itau_w, & + gr_phy_write_3d(d_tr_cv(:, :, it))) + CALL histwrite(nid_tra, "d_tr_cl_"//tnom(it+2), itau_w, & + gr_phy_write_3d(d_tr_cl(:, :, it))) ENDDO - CALL gr_fi_ecrit(llm, klon, iim, jjm+1, pplay, zx_tmp_3d) - 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) + CALL histwrite(nid_tra, "pplay", itau_w, gr_phy_write_3d(pplay)) + CALL histwrite(nid_tra, "T", itau_w, gr_phy_write_3d(t_seri)) if (ok_sync) then call histsync(nid_tra)