--- trunk/phylmd/Interface_surf/calcul_fluxs.f 2018/04/19 17:54:55 266 +++ trunk/phylmd/Interface_surf/calcul_fluxs.f 2018/09/18 15:14:40 308 @@ -4,22 +4,26 @@ contains - SUBROUTINE calcul_fluxs(dtime, tsurf, p1lay, cal, beta, coef1lay, ps, & - qsurf, radsol, dif_grnd, t1lay, q1lay, u1lay, v1lay, petAcoef, & - peqAcoef, petBcoef, peqBcoef, tsurf_new, evap, fluxlat, flux_t, & - dflux_s, dflux_l) + SUBROUTINE calcul_fluxs(tsurf, p1lay, cal, beta, cdragh, ps, qsurf, & + radsol, t1lay, q1lay, u1lay, v1lay, tAcoef, qAcoef, tBcoef, & + qBcoef, tsurf_new, evap, fluxlat, flux_t, dflux_s, dflux_l, dif_grnd) ! Cette routine calcule les flux en h et q à l'interface et une ! température de surface. ! L. Fairhead, April 2000 - USE fcttre, ONLY: foede, foeew + ! Note that, if cal = 0, beta = 1 and dif_grnd = 0, then tsurf_new + ! = tsurf and qsurf = qsat. + + ! Libraries: use nr_util, only: assert_eq + + use comconst, only: dtphys + USE fcttre, ONLY: foede, foeew USE suphec_m, ONLY: rcpd, rd, retv, rlstt, rlvtt, rtt USE yoethf_m, ONLY: r2es, r5ies, r5les, rvtmp2 - real, intent(IN):: dtime real, intent(IN):: tsurf(:) ! (knon) température de surface real, intent(IN):: p1lay(:) ! (knon) @@ -27,22 +31,20 @@ real, intent(IN):: cal(:) ! (knon) capacité calorifique du sol real, intent(IN):: beta(:) ! (knon) évaporation réelle - real, intent(IN):: coef1lay(:) ! (knon) coefficient d'échange + real, intent(IN):: cdragh(:) ! (knon) coefficient d'échange real, intent(IN):: ps(:) ! (knon) pression au sol real, intent(OUT):: qsurf(:) ! (knon) humidité de l'air au-dessus du sol real, intent(IN):: radsol(:) ! (knon) ! rayonnement net au sol (longwave + shortwave) - real, intent(IN):: dif_grnd(:) ! (knon) - ! coefficient de diffusion vers le sol profond - + real, intent(IN):: dif_grnd ! coefficient de diffusion vers le sol profond real, intent(IN):: t1lay(:), q1lay(:), u1lay(:), v1lay(:) ! (knon) - real, intent(IN):: petAcoef(:), peqAcoef(:) ! (knon) + real, intent(IN):: tAcoef(:), qAcoef(:) ! (knon) ! coefficients A de la résolution de la couche limite pour T et q - real, intent(IN):: petBcoef(:), peqBcoef(:) ! (knon) + real, intent(IN):: tBcoef(:), qBcoef(:) ! (knon) ! coefficients B de la résolution de la couche limite pour t et q real, intent(OUT):: tsurf_new(:) ! (knon) température au sol @@ -57,22 +59,23 @@ ! Local: integer i - integer knon ! nombre de points a traiter + integer knon ! nombre de points \`a traiter real, dimension(size(ps)):: mh, oh, mq, nq, oq, dq_s_dt, coef ! (knon) real qsat(size(ps)) ! (knon) mass fraction real sl(size(ps)) ! (knon) chaleur latente d'évaporation ou de sublimation logical delta real zcor real, parameter:: t_grnd = 271.35 + real, parameter:: min_wind_speed = 1. ! in m s-1 !--------------------------------------------------------------------- - knon = assert_eq((/size(tsurf), size(p1lay), size(cal), size(beta), & - size(coef1lay), size(ps), size(qsurf), size(radsol), size(dif_grnd), & - size(t1lay), size(q1lay), size(u1lay), size(v1lay), size(petAcoef), & - size(peqAcoef), size(petBcoef), size(peqBcoef), size(tsurf_new), & - size(evap), size(fluxlat), size(flux_t), size(dflux_s), & - size(dflux_l)/), "calcul_fluxs knon") + knon = assert_eq([size(tsurf), size(p1lay), size(cal), size(beta), & + size(cdragh), size(ps), size(qsurf), size(radsol), size(t1lay), & + size(q1lay), size(u1lay), size(v1lay), size(tAcoef), size(qAcoef), & + size(tBcoef), size(qBcoef), size(tsurf_new), size(evap), & + size(fluxlat), size(flux_t), size(dflux_s), size(dflux_l)], & + "calcul_fluxs knon") ! Traitement de l'humidité du sol @@ -86,31 +89,28 @@ qsat(i), zcor) / RLVTT ENDDO - coef = coef1lay * (1. + SQRT(u1lay**2 + v1lay**2)) * p1lay / (RD * t1lay) + coef = cdragh * (min_wind_speed + SQRT(u1lay**2 + v1lay**2)) * p1lay & + / (RD * t1lay) sl = merge(RLSTT, RLVTT, tsurf < RTT) ! Q - oq = 1. - beta * coef * peqBcoef * dtime - mq = beta * coef * (peqAcoef - qsat + dq_s_dt * tsurf) / oq - nq = beta * coef * (- 1. * dq_s_dt) / oq + oq = 1. - beta * coef * qBcoef * dtphys + mq = beta * coef * (qAcoef - qsat + dq_s_dt * tsurf) / oq + nq = - beta * coef * dq_s_dt / oq ! H - oh = 1. - (coef * petBcoef * dtime) - mh = coef * petAcoef / oh - dflux_s = - (coef * RCPD)/ oh - - ! Tsurface - tsurf_new = (tsurf + cal / RCPD * dtime * (radsol + mh + sl * mq) & - + dif_grnd * t_grnd * dtime) / (1. - dtime * cal / RCPD * (dflux_s & - + sl * nq) + dtime * dif_grnd) - + oh = 1. - coef * tBcoef * dtphys + mh = coef * tAcoef / oh + dflux_s = - coef * RCPD / oh + + tsurf_new = (tsurf + cal / RCPD * dtphys * (radsol + mh + sl * mq) & + + dif_grnd * t_grnd * dtphys) / (1. - dtphys * cal / RCPD * (dflux_s & + + sl * nq) + dtphys * dif_grnd) evap = - mq - nq * tsurf_new fluxlat = - evap * sl flux_t = mh + dflux_s * tsurf_new dflux_l = sl * nq - - ! Nouvelle valeur de l'humidité au dessus du sol : - qsurf = (peqAcoef - peqBcoef * evap * dtime) * (1. - beta) + beta * (qsat & + qsurf = (qAcoef - qBcoef * evap * dtphys) * (1. - beta) + beta * (qsat & + dq_s_dt * (tsurf_new - tsurf)) END SUBROUTINE calcul_fluxs