--- trunk/phylmd/Interface_surf/pbl_surface.f 2018/09/27 14:58:10 309 +++ trunk/phylmd/Interface_surf/pbl_surface.f90 2019/06/13 14:40:06 328 @@ -6,7 +6,7 @@ SUBROUTINE pbl_surface(pctsrf, t, q, u, v, julien, mu0, ftsol, cdmmax, & cdhmax, ftsoil, qsol, paprs, play, fsnow, fqsurf, falbe, fluxlat, & - rain_fall, snow_fall, frugs, agesno, rugoro, d_t, d_q, d_u, d_v, d_ts, & + rain_fall, snow_fall, frugs, agesno, rugoro, d_t, d_q, d_u, d_v, & 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, albsol, sollw, solsw, & @@ -34,12 +34,12 @@ USE histwrite_phy_m, ONLY: histwrite_phy USE indicesol, ONLY: epsfra, is_lic, is_oce, is_sic, is_ter, nbsrf USE interfoce_lim_m, ONLY: interfoce_lim - use phyetat0_m, only: zmasq + use phyetat0_m, only: masque use stdlevvar_m, only: stdlevvar USE suphec_m, ONLY: rd, rg, rsigma use time_phylmdz, only: itap - REAL, INTENT(inout):: pctsrf(klon, nbsrf) + REAL, INTENT(inout):: pctsrf(:, :) ! (klon, nbsrf) ! pourcentages de surface de chaque maille REAL, INTENT(IN):: t(klon, klev) ! temperature (K) @@ -47,7 +47,10 @@ REAL, INTENT(IN):: u(klon, klev), v(klon, klev) ! vitesse INTEGER, INTENT(IN):: julien ! jour de l'annee en cours REAL, intent(in):: mu0(klon) ! cosinus de l'angle solaire zenithal - REAL, INTENT(IN):: ftsol(:, :) ! (klon, nbsrf) temp\'erature du sol (en K) + + REAL, INTENT(INout):: ftsol(:, :) ! (klon, nbsrf) + ! skin temperature of surface fraction, in K + REAL, INTENT(IN):: cdmmax, cdhmax ! seuils cdrm, cdrh REAL, INTENT(inout):: ftsoil(klon, nsoilmx, nbsrf) @@ -61,7 +64,9 @@ REAL, INTENT(inout):: fsnow(:, :) ! (klon, nbsrf) \'epaisseur neigeuse REAL, INTENT(inout):: fqsurf(klon, nbsrf) REAL, intent(inout):: falbe(klon, nbsrf) + REAL, intent(out):: fluxlat(:, :) ! (klon, nbsrf) + ! flux de chaleur latente, en W m-2 REAL, intent(in):: rain_fall(klon) ! liquid water mass flux (kg / m2 / s), positive down @@ -79,13 +84,11 @@ REAL, intent(out):: d_u(klon, klev), d_v(klon, klev) ! changement pour "u" et "v" - REAL, intent(out):: d_ts(:, :) ! (klon, nbsrf) variation of ftsol - REAL, intent(out):: flux_t(klon, nbsrf) ! flux de chaleur sensible (c_p T) (W / m2) (orientation positive ! vers le bas) à la surface - REAL, intent(out):: flux_q(klon, nbsrf) + REAL, intent(out):: flux_q(klon, nbsrf) ! flux de vapeur d'eau (kg / m2 / s) à la surface REAL, intent(out):: flux_u(:, :), flux_v(:, :) ! (klon, nbsrf) @@ -139,6 +142,7 @@ ! Local: + REAL d_ts(klon, nbsrf) ! variation of ftsol REAL fsollw(klon, nbsrf) ! bilan flux IR pour chaque sous-surface REAL fsolsw(klon, nbsrf) ! flux solaire absorb\'e pour chaque sous-surface @@ -250,8 +254,8 @@ pctsrf_pot(:, is_ter) = pctsrf(:, is_ter) pctsrf_pot(:, is_lic) = pctsrf(:, is_lic) - pctsrf_pot(:, is_oce) = 1. - zmasq - pctsrf_pot(:, is_sic) = 1. - zmasq + pctsrf_pot(:, is_oce) = 1. - masque + pctsrf_pot(:, is_sic) = 1. - masque ! Tester si c'est le moment de lire le fichier: if (mod(itap - 1, lmt_pas) == 0) then @@ -502,6 +506,11 @@ pctsrf(:, is_sic) = pctsrf_new_sic CALL histwrite_phy("run_off_lic", run_off_lic) + ftsol = ftsol + d_ts ! update surface temperature + CALL histwrite_phy("dtsvdfo", d_ts(:, is_oce)) + CALL histwrite_phy("dtsvdft", d_ts(:, is_ter)) + CALL histwrite_phy("dtsvdfg", d_ts(:, is_lic)) + CALL histwrite_phy("dtsvdfi", d_ts(:, is_sic)) END SUBROUTINE pbl_surface