--- trunk/phylmd/phytrac.f 2014/12/18 17:30:24 118 +++ trunk/Sources/phylmd/phytrac.f 2015/09/29 19:48:59 171 @@ -9,8 +9,8 @@ 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, pphis, da, & - phi, mp, upwd, dnwd, tr_seri, zmasse) + entr_therm, yu1, yv1, ftsol, pctsrf, frac_impa, frac_nucl, da, phi, & + mp, upwd, dnwd, tr_seri, zmasse, ncid_startphy, nid_ins) ! From phylmd/phytrac.F, version 1.15 2006/02/21 08:08:30 (SVN revision 679) @@ -29,18 +29,22 @@ use abort_gcm_m, only: abort_gcm use clesphys, only: ecrit_tra use clesphys2, only: iflag_con + use cltrac_m, only: cltrac use cltracrn_m, only: cltracrn use ctherm, only: iflag_thermals + use cvltr_m, only: cvltr use dimens_m, only: llm, nqmx use dimphy, only: klon use indicesol, only: nbsrf - use ini_histrac_m, only: ini_histrac use initrrnpb_m, only: initrrnpb use minmaxqfi_m, only: minmaxqfi + use netcdf, only: NF90_FILL_float + use netcdf95, only: nf95_inq_varid, nf95_get_var, nf95_put_var use nflxtr_m, only: nflxtr use nr_util, only: assert use o3_chem_m, only: o3_chem use phyetat0_m, only: rlat + use phyredem0_m, only: ncid_restartphy use press_coefoz_m, only: press_coefoz use radiornpb_m, only: radiornpb use regr_pr_comb_coefoz_m, only: regr_pr_comb_coefoz @@ -87,8 +91,6 @@ REAL frac_impa(klon, llm) ! fraction d'aerosols impactes REAL frac_nucl(klon, llm) ! fraction d'aerosols nuclees - real, intent(in):: pphis(klon) - ! Kerry Emanuel real, intent(in):: da(klon, llm), phi(klon, llm, llm), mp(klon, llm) REAL, intent(in):: upwd(klon, llm) ! saturated updraft mass flux @@ -100,7 +102,9 @@ 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, intent(in):: ncid_startphy, nid_ins + + ! Local: integer nsplit @@ -114,7 +118,7 @@ ! ! Pour la source de radon et son reservoir de sol - REAL, save:: trs(klon, nqmx - 2) ! Concentration de radon dans le sol + REAL, save:: trs(klon, nqmx - 2) ! Concentration de traceur dans le sol REAL masktr(klon, nqmx - 2) ! Masque reservoir de sol traceur ! Masque de l'echange avec la surface @@ -132,7 +136,6 @@ SAVE scavtr CHARACTER itn - INTEGER, save:: nid_tra ! nature du traceur @@ -153,7 +156,10 @@ REAL d_tr(klon, llm), d_trs(klon) ! tendances de traceurs REAL d_tr_cl(klon, llm, nqmx - 2) ! tendance de traceurs couche limite - REAL d_tr_cv(klon, llm, nqmx - 2) ! tendance de traceurs conv pour chq traceur + + REAL d_tr_cv(klon, llm, nqmx - 2) + ! tendance de traceurs conv pour chq traceur + 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 @@ -165,7 +171,7 @@ ! ! dans chaque couche real ztra_th(klon, llm) - integer isplit + integer isplit, varid ! Controls: logical:: couchelimite = .true. @@ -183,18 +189,14 @@ PRINT *, 'Frequency of tracer output: ecrit_tra = ', ecrit_tra inirnpb = .true. - ! Initialisation des sorties : - call ini_histrac(nid_tra, pdtphys, nqmx - 2, lessivage) - ! Initialisation de certaines variables pour le radon et le plomb ! Initialisation du traceur dans le sol (couche limite radonique) - trs(:, :) = 0. + trs(:, 2:) = 0. - open (unit=99, file='starttrac', status='old', err=999, & - form='formatted') - read(unit=99, fmt=*) (trs(i, 1), i=1, klon) -999 continue - close(unit=99) + call nf95_inq_varid(ncid_startphy, "trs", varid) + call nf95_get_var(ncid_startphy, varid, trs(:, 1)) + if (any(trs(:, 1) == NF90_FILL_float)) call abort_gcm("phytrac", & + "some missing values in trs(:, 1)") ! Initialisation de la fraction d'aerosols lessivee @@ -234,8 +236,8 @@ tr_seri(:, :, it), d_tr_cv(:, :, 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)) + call cvltr(pdtphys, da, phi, mp, paprs, tr_seri(:, :, it), upwd, & + dnwd, d_tr_cv(:, :, it)) endif DO k = 1, llm @@ -294,35 +296,26 @@ 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(1, 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) + 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 - ! Traceur ds sol - - DO i = 1, klon - trs(i, it) = trs(i, it) + d_trs(i) - END DO - else ! couche limite avec flux prescrit + 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.0 ! pas de source, pour l'instant + source(i) = 0. ! pas de source, pour l'instant ENDDO - CALL cltrac(pdtphys, coefh, t_seri, & - tr_seri(1, 1, it), source, & - paprs, pplay, delp, & - d_tr_cl(1, 1, it)) + 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) @@ -349,7 +342,7 @@ ! Ozone as a tracer: if (mod(itap - 1, lmt_pas) == 0) then ! Once per day, update the coefficients for ozone chemistry: - call regr_pr_comb_coefoz(julien) + call regr_pr_comb_coefoz(julien, paprs, pplay) end if call o3_chem(julien, gmtime, t_seri, zmasse, pdtphys, tr_seri(:, :, 3)) end if @@ -404,21 +397,16 @@ ENDIF ! Ecriture des sorties - call write_histrac(lessivage, itap, nid_tra) + call write_histrac(lessivage, itap, nid_ins) if (lafin) then - print *, "C'est la fin de la physique." - open(unit=99, file='restarttrac', form='formatted') - do i=1, klon - write(unit=99, fmt=*) trs(i, 1) - enddo - PRINT *, 'Ecriture du fichier restarttrac' - close(unit=99) + 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_tra) + subroutine write_histrac(lessivage, itap, nid_ins) ! From phylmd/write_histrac.h, version 1.9 2006/02/21 08:08:30 @@ -426,51 +414,40 @@ use histsync_m, only: histsync use histwrite_m, only: histwrite use temps, only: itau_phy - use iniadvtrac_m, only: tnom - use comgeomphy, only: airephy + use iniadvtrac_m, only: tname 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):: itap ! number of calls to "physiq" - integer, intent(in):: nid_tra + integer, intent(in):: nid_ins ! Variables local to the procedure: integer it integer itau_w ! pas de temps ecriture - logical, parameter:: ok_sync = .true. !----------------------------------------------------- itau_w = itau_phy + itap - 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)) + CALL histwrite(nid_ins, "zmasse", itau_w, gr_phy_write_3d(zmasse)) DO it=1, nqmx - 2 - CALL histwrite(nid_tra, tnom(it+2), itau_w, & + CALL histwrite(nid_ins, tname(it+2), itau_w, & gr_phy_write_3d(tr_seri(:, :, it))) if (lessivage) THEN - CALL histwrite(nid_tra, "fl"//tnom(it+2), itau_w, & + CALL histwrite(nid_ins, "fl"//tname(it+2), itau_w, & gr_phy_write_3d(flestottr(:, :, it))) endif - CALL histwrite(nid_tra, "d_tr_th_"//tnom(it+2), itau_w, & + CALL histwrite(nid_ins, "d_tr_th_"//tname(it+2), itau_w, & gr_phy_write_3d(d_tr_th(:, :, it))) - CALL histwrite(nid_tra, "d_tr_cv_"//tnom(it+2), itau_w, & + CALL histwrite(nid_ins, "d_tr_cv_"//tname(it+2), itau_w, & gr_phy_write_3d(d_tr_cv(:, :, it))) - CALL histwrite(nid_tra, "d_tr_cl_"//tnom(it+2), itau_w, & + CALL histwrite(nid_ins, "d_tr_cl_"//tname(it+2), itau_w, & gr_phy_write_3d(d_tr_cl(:, :, it))) ENDDO - 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) - endif - end subroutine write_histrac END SUBROUTINE phytrac