--- trunk/phylmd/physiq.f 2018/05/03 16:14:08 267 +++ trunk/phylmd/physiq.f 2018/09/11 12:23:47 306 @@ -20,6 +20,7 @@ use calltherm_m, only: calltherm USE clesphys, ONLY: cdhmax, cdmmax, ecrit_ins, ok_instan USE clesphys2, ONLY: conv_emanuel, nbapp_rad, new_oliq, ok_orodr, ok_orolf + USE conf_interface_m, ONLY: conf_interface USE pbl_surface_m, ONLY: pbl_surface use clouds_gno_m, only: clouds_gno use comconst, only: dtphys @@ -149,7 +150,6 @@ REAL, save:: ftsoil(klon, nsoilmx, nbsrf) ! soil temperature of surface fraction - REAL, save:: fevap(klon, nbsrf) ! evaporation REAL fluxlat(klon, nbsrf) REAL, save:: fqsurf(klon, nbsrf) @@ -187,11 +187,11 @@ REAL, save:: ffonte(klon, nbsrf) ! flux thermique utilise pour fondre la neige - REAL, save:: fqcalving(klon, nbsrf) - ! flux d'eau "perdue" par la surface et necessaire pour limiter la - ! hauteur de neige, en kg / m2 / s + REAL fqcalving(klon, nbsrf) + ! flux d'eau "perdue" par la surface et n\'ecessaire pour limiter + ! la hauteur de neige, en kg / m2 / s - REAL zxffonte(klon), zxfqcalving(klon) + REAL zxffonte(klon) REAL, save:: pfrac_impa(klon, llm)! Produits des coefs lessivage impaction REAL, save:: pfrac_nucl(klon, llm)! Produits des coefs lessivage nucleation @@ -211,9 +211,9 @@ REAL rain_tiedtke(klon), snow_tiedtke(klon) REAL evap(klon) ! flux d'\'evaporation au sol - real devap(klon) ! derivative of the evaporation flux at the surface + real dflux_q(klon) ! derivative of the evaporation flux at the surface REAL sens(klon) ! flux de chaleur sensible au sol - real dsens(klon) ! derivee du flux de chaleur sensible au sol + real dflux_t(klon) ! derivee du flux de chaleur sensible au sol REAL, save:: dlw(klon) ! derivative of infra-red flux REAL bils(klon) ! bilan de chaleur au sol REAL fder(klon) ! Derive de flux (sensible et latente) @@ -326,9 +326,9 @@ INTEGER, save:: ibas_con(klon), itop_con(klon) real ema_pct(klon) ! Emanuel pressure at cloud top, in Pa - REAL, save:: rain_con(klon) + REAL rain_con(klon) real rain_lsc(klon) - REAL, save:: snow_con(klon) ! neige (mm / s) + REAL snow_con(klon) ! neige (mm / s) real snow_lsc(klon) REAL d_ts(klon, nbsrf) ! variation of ftsol @@ -417,9 +417,6 @@ t2m = 0. q2m = 0. ffonte = 0. - fqcalving = 0. - rain_con = 0. - snow_con = 0. d_u_con = 0. d_v_con = 0. rnebcon0 = 0. @@ -446,10 +443,10 @@ frugs = 0. CALL phyetat0(pctsrf, ftsol, ftsoil, fqsurf, qsol, fsnow, falbe, & - fevap, rain_fall, snow_fall, solsw, sollw, dlw, radsol, frugs, & - agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, & - q_ancien, ancien_ok, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, & - w01, ncid_startphy) + rain_fall, snow_fall, solsw, sollw, dlw, radsol, frugs, agesno, & + zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, q_ancien, & + ancien_ok, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01, & + ncid_startphy) ! ATTENTION : il faudra a terme relire q2 dans l'etat initial q2 = 1e-8 @@ -470,12 +467,10 @@ rugoro = 0. ENDIF - ecrit_ins = NINT(ecrit_ins / dtphys) - ! Initialisation des sorties - - call ini_histins(dtphys, ok_newmicro) + call ini_histins(ok_newmicro) CALL phyredem0 + call conf_interface ENDIF test_firstcal ! We will modify variables *_seri and we will not touch variables @@ -553,11 +548,11 @@ fsolsw(:, nsrf) = solsw * (1. - falbe(:, nsrf)) / (1. - albsol) END forall - CALL pbl_surface(dtphys, pctsrf, t_seri, q_seri, u_seri, v_seri, julien, & - mu0, ftsol, cdmmax, cdhmax, ftsoil, qsol, paprs, play, fsnow, fqsurf, & - fevap, falbe, fluxlat, rain_fall, snow_fall, fsolsw, fsollw, frugs, & - agesno, rugoro, d_t_vdf, d_q_vdf, d_u_vdf, d_v_vdf, d_ts, flux_t, & - flux_q, flux_u, flux_v, cdragh, cdragm, q2, dsens, devap, coefh, t2m, & + CALL pbl_surface(pctsrf, t_seri, q_seri, u_seri, v_seri, julien, mu0, & + ftsol, cdmmax, cdhmax, ftsoil, qsol, paprs, play, fsnow, fqsurf, & + falbe, fluxlat, rain_fall, snow_fall, fsolsw, fsollw, frugs, agesno, & + rugoro, d_t_vdf, d_q_vdf, d_u_vdf, d_v_vdf, d_ts, flux_t, flux_q, & + flux_u, flux_v, cdragh, cdragm, q2, dflux_t, dflux_q, coefh, t2m, & q2m, u10m_srf, v10m_srf, pblh, capCL, oliqCL, cteiCL, pblT, therm, & plcl, fqcalving, ffonte, run_off_lic_0) @@ -565,7 +560,7 @@ sens = - sum(flux_t * pctsrf, dim = 2) evap = - sum(flux_q * pctsrf, dim = 2) - fder = dlw + dsens + devap + fder = dlw + dflux_t + dflux_q DO k = 1, llm DO i = 1, klon @@ -576,10 +571,8 @@ ENDDO ENDDO - ! Update surface temperature: - call assert(abs(sum(pctsrf, dim = 2) - 1.) <= EPSFRA, 'physiq: pctsrf') - ftsol = ftsol + d_ts + ftsol = ftsol + d_ts ! update surface temperature tsol = sum(ftsol * pctsrf, dim = 2) zxfluxlat = sum(fluxlat * pctsrf, dim = 2) zt2m = sum(t2m * pctsrf, dim = 2) @@ -587,7 +580,6 @@ u10m = sum(u10m_srf * pctsrf, dim = 2) v10m = sum(v10m_srf * pctsrf, dim = 2) zxffonte = sum(ffonte * pctsrf, dim = 2) - zxfqcalving = sum(fqcalving * pctsrf, dim = 2) s_pblh = sum(pblh * pctsrf, dim = 2) s_lcl = sum(plcl * pctsrf, dim = 2) s_capCL = sum(capCL * pctsrf, dim = 2) @@ -606,7 +598,6 @@ u10m_srf(i, nsrf) = u10m(i) v10m_srf(i, nsrf) = v10m(i) ffonte(i, nsrf) = zxffonte(i) - fqcalving(i, nsrf) = zxfqcalving(i) pblh(i, nsrf) = s_pblh(i) plcl(i, nsrf) = s_lcl(i) capCL(i, nsrf) = s_capCL(i) @@ -647,10 +638,10 @@ conv_q = d_q_dyn + d_q_vdf / dtphys conv_t = d_t_dyn + d_t_vdf / dtphys z_avant = sum((q_seri + ql_seri) * zmasse, dim=2) - CALL conflx(dtphys, paprs, play, t_seri(:, llm:1:- 1), & - q_seri(:, llm:1:- 1), conv_t, conv_q, - evap, omega, d_t_con, & - d_q_con, rain_con, snow_con, mfu(:, llm:1:- 1), mfd(:, llm:1:- 1), & - pen_u, pde_u, pen_d, pde_d, kcbot, kctop, kdtop, pmflxr, pmflxs) + CALL conflx(paprs, play, t_seri(:, llm:1:- 1), q_seri(:, llm:1:- 1), & + conv_t, conv_q, - evap, omega, d_t_con, d_q_con, rain_con, & + snow_con, mfu(:, llm:1:- 1), mfd(:, llm:1:- 1), pen_u, pde_u, & + pen_d, pde_d, kcbot, kctop, kdtop, pmflxr, pmflxs) WHERE (rain_con < 0.) rain_con = 0. WHERE (snow_con < 0.) snow_con = 0. ibas_con = llm + 1 - kcbot @@ -693,8 +684,8 @@ t_seri = t_seri + d_t_ajs q_seri = q_seri + d_q_ajs else - call calltherm(dtphys, play, paprs, pphi, u_seri, v_seri, t_seri, & - q_seri, d_u_ajs, d_v_ajs, d_t_ajs, d_q_ajs, fm_therm, entr_therm) + call calltherm(play, paprs, pphi, u_seri, v_seri, t_seri, q_seri, & + d_u_ajs, d_v_ajs, d_t_ajs, d_q_ajs, fm_therm, entr_therm) endif ! Caclul des ratqs @@ -735,7 +726,7 @@ ratqs = ratqss endif - CALL fisrtilp(dtphys, paprs, play, t_seri, q_seri, ptconv, ratqs, d_t_lsc, & + CALL fisrtilp(paprs, play, t_seri, q_seri, ptconv, ratqs, d_t_lsc, & d_q_lsc, d_ql_lsc, rneb, cldliq, rain_lsc, snow_lsc, pfrac_impa, & pfrac_nucl, pfrac_1nucl, frac_impa, frac_nucl, prfl, psfl, rhcl) @@ -881,9 +872,9 @@ ENDIF ENDDO - CALL drag_noro(dtphys, paprs, play, zmea, zstd, zsig, zgam, zthe, & - zpic, zval, ktest, t_seri, u_seri, v_seri, zulow, zvlow, zustrdr, & - zvstrdr, d_t_oro, d_u_oro, d_v_oro) + CALL drag_noro(paprs, play, zmea, zstd, zsig, zgam, zthe, zpic, zval, & + ktest, t_seri, u_seri, v_seri, zulow, zvlow, zustrdr, zvstrdr, & + d_t_oro, d_u_oro, d_v_oro) ! ajout des tendances DO k = 1, llm @@ -904,9 +895,8 @@ ENDIF ENDDO - CALL lift_noro(dtphys, paprs, play, zmea, zstd, zpic, ktest, t_seri, & - u_seri, v_seri, zulow, zvlow, zustrli, zvstrli, d_t_lif, & - d_u_lif, d_v_lif) + CALL lift_noro(paprs, play, zmea, zstd, zpic, ktest, t_seri, u_seri, & + v_seri, zulow, zvlow, zustrli, zvstrli, d_t_lif, d_u_lif, d_v_lif) ! Ajout des tendances : DO k = 1, llm @@ -924,10 +914,10 @@ aam, torsfc) ! Calcul des tendances traceurs - call phytrac(julien, time, firstcal, lafin, dtphys, t, paprs, play, mfu, & - mfd, pde_u, pen_d, coefh, cdragh, fm_therm, entr_therm, u(:, 1), & - v(:, 1), ftsol, pctsrf, frac_impa, frac_nucl, da, phi, mp, upwd, & - dnwd, tr_seri, zmasse, ncid_startphy) + call phytrac(julien, time, firstcal, lafin, t, paprs, play, mfu, mfd, & + pde_u, pen_d, coefh, cdragh, fm_therm, entr_therm, u(:, 1), v(:, 1), & + ftsol, pctsrf, frac_impa, frac_nucl, da, phi, mp, upwd, dnwd, & + tr_seri, zmasse, ncid_startphy) ! Calculer le transport de l'eau et de l'energie (diagnostique) CALL transp(paprs, t_seri, q_seri, u_seri, v_seri, zphi, ve, vq, ue, uq) @@ -1013,21 +1003,7 @@ CALL histwrite_phy("dtsvdft", d_ts(:, is_ter)) CALL histwrite_phy("dtsvdfg", d_ts(:, is_lic)) CALL histwrite_phy("dtsvdfi", d_ts(:, is_sic)) - - DO nsrf = 1, nbsrf - CALL histwrite_phy("pourc_"//clnsurf(nsrf), pctsrf(:, nsrf) * 100.) - CALL histwrite_phy("fract_"//clnsurf(nsrf), pctsrf(:, nsrf)) - CALL histwrite_phy("sens_"//clnsurf(nsrf), flux_t(:, nsrf)) - CALL histwrite_phy("lat_"//clnsurf(nsrf), fluxlat(:, nsrf)) - CALL histwrite_phy("tsol_"//clnsurf(nsrf), ftsol(:, nsrf)) - CALL histwrite_phy("taux_"//clnsurf(nsrf), flux_u(:, nsrf)) - CALL histwrite_phy("tauy_"//clnsurf(nsrf), flux_v(:, nsrf)) - CALL histwrite_phy("rugs_"//clnsurf(nsrf), frugs(:, nsrf)) - CALL histwrite_phy("albe_"//clnsurf(nsrf), falbe(:, nsrf)) - CALL histwrite_phy("u10m_"//clnsurf(nsrf), u10m_srf(:, nsrf)) - CALL histwrite_phy("v10m_"//clnsurf(nsrf), v10m_srf(:, nsrf)) - END DO - + CALL histwrite_phy("zxfqcalving", sum(fqcalving * pctsrf, dim = 2)) CALL histwrite_phy("albs", albsol) CALL histwrite_phy("tro3", wo * dobson_u * 1e3 / zmasse / rmo3 * md) CALL histwrite_phy("rugs", zxrugs) @@ -1038,12 +1014,6 @@ CALL histwrite_phy("s_oliqCL", s_oliqCL) CALL histwrite_phy("s_cteiCL", s_cteiCL) CALL histwrite_phy("s_therm", s_therm) - - if (conv_emanuel) then - CALL histwrite_phy("ptop", ema_pct) - CALL histwrite_phy("dnwd0", - mp) - end if - CALL histwrite_phy("temp", t_seri) CALL histwrite_phy("vitu", u_seri) CALL histwrite_phy("vitv", v_seri) @@ -1057,16 +1027,35 @@ CALL histwrite_phy("dtlw0", - cool0 / 86400.) CALL histwrite_phy("msnow", sum(fsnow * pctsrf, dim = 2)) call histwrite_phy("qsurf", sum(fqsurf * pctsrf, dim = 2)) + call histwrite_phy("flat", zxfluxlat) + + DO nsrf = 1, nbsrf + CALL histwrite_phy("pourc_"//clnsurf(nsrf), pctsrf(:, nsrf) * 100.) + CALL histwrite_phy("fract_"//clnsurf(nsrf), pctsrf(:, nsrf)) + CALL histwrite_phy("sens_"//clnsurf(nsrf), flux_t(:, nsrf)) + CALL histwrite_phy("lat_"//clnsurf(nsrf), fluxlat(:, nsrf)) + CALL histwrite_phy("tsol_"//clnsurf(nsrf), ftsol(:, nsrf)) + CALL histwrite_phy("taux_"//clnsurf(nsrf), flux_u(:, nsrf)) + CALL histwrite_phy("tauy_"//clnsurf(nsrf), flux_v(:, nsrf)) + CALL histwrite_phy("rugs_"//clnsurf(nsrf), frugs(:, nsrf)) + CALL histwrite_phy("albe_"//clnsurf(nsrf), falbe(:, nsrf)) + CALL histwrite_phy("u10m_"//clnsurf(nsrf), u10m_srf(:, nsrf)) + CALL histwrite_phy("v10m_"//clnsurf(nsrf), v10m_srf(:, nsrf)) + END DO + + if (conv_emanuel) then + CALL histwrite_phy("ptop", ema_pct) + CALL histwrite_phy("dnwd0", - mp) + end if if (ok_instan) call histsync(nid_ins) IF (lafin) then call NF95_CLOSE(ncid_startphy) - CALL phyredem(pctsrf, ftsol, ftsoil, fqsurf, qsol, & - fsnow, falbe, fevap, rain_fall, snow_fall, solsw, sollw, dlw, & - radsol, frugs, agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, & - t_ancien, q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, & - w01) + CALL phyredem(pctsrf, ftsol, ftsoil, fqsurf, qsol, fsnow, falbe, & + rain_fall, snow_fall, solsw, sollw, dlw, radsol, frugs, agesno, & + zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, q_ancien, & + rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01) end IF firstcal = .FALSE.