--- trunk/Sources/phylmd/Interface_surf/fonte_neige.f 2017/03/30 14:25:18 217 +++ trunk/phylmd/Interface_surf/fonte_neige.f 2018/08/02 17:23:07 301 @@ -4,22 +4,21 @@ contains - SUBROUTINE fonte_neige(nisurf, dtime, precip_rain, precip_snow, snow, qsol, & - tsurf_new, evap, fqcalving, ffonte, run_off_lic_0) + SUBROUTINE fonte_neige(nisurf, precip_rain, precip_snow, snow, qsol, & + tsurf_new, evap, fqcalving, ffonte, run_off_lic_0, run_off_lic) ! Routine de traitement de la fonte de la neige dans le cas du traitement ! de sol simplifi\'e ! Laurent Fairhead, March, 2001 - USE fcttre, ONLY: foeew, qsatl, qsats + use comconst, only: dtphys USE indicesol, ONLY: epsfra, is_lic, is_sic, is_ter - USE interface_surf, ONLY: tau_calv + USE conf_interface_m, ONLY: tau_calv use nr_util, only: assert_eq USE suphec_m, ONLY: rday, rlmlt, rtt integer, intent(IN):: nisurf ! surface \`a traiter - real, intent(IN):: dtime ! pas de temps de la physique (en s) real, intent(IN):: precip_rain(:) ! (knon) ! precipitation, liquid water mass flux (kg / m2 / s), positive down @@ -46,6 +45,8 @@ real, intent(INOUT):: run_off_lic_0(:) ! (knon) ! run off glacier du pas de temps pr\'ecedent + REAL, intent(OUT):: run_off_lic(:) ! (knon) ruissellement total + ! Local: integer knon ! nombre de points \`a traiter @@ -61,7 +62,6 @@ REAL, parameter:: chaice = 3.334E5 / (2.3867E6 * 0.15) real, parameter:: max_eau_sol = 150. ! in kg m-2 real coeff_rel - REAL, ALLOCATABLE, SAVE:: run_off_lic(:) ! ruissellement total !-------------------------------------------------------------------- @@ -69,18 +69,18 @@ size(qsol), size(tsurf_new), size(evap), size(fqcalving), & size(ffonte), size(run_off_lic_0)/), "fonte_neige knon") - coeff_rel = dtime / (tau_calv * rday) - WHERE (precip_snow > 0.) snow = snow + precip_snow * dtime + coeff_rel = dtphys / (tau_calv * rday) + WHERE (precip_snow > 0.) snow = snow + precip_snow * dtphys WHERE (evap > 0.) - snow_evap = MIN(snow / dtime, evap) - snow = snow - snow_evap * dtime + snow_evap = MIN(snow / dtphys, evap) + snow = snow - snow_evap * dtphys snow = MAX(0., snow) elsewhere snow_evap = 0. end where - bil_eau_s = (precip_rain - evap + snow_evap) * dtime + bil_eau_s = (precip_rain - evap + snow_evap) * dtphys ! Y a-t-il fonte de neige ? @@ -88,7 +88,7 @@ if ((snow(i) > epsfra .OR. nisurf == is_sic & .OR. nisurf == is_lic) .AND. tsurf_new(i) >= RTT) then fq_fonte = MIN(MAX((tsurf_new(i) - RTT) / chasno, 0.), snow(i)) - ffonte(i) = fq_fonte * RLMLT / dtime + ffonte(i) = fq_fonte * RLMLT / dtphys snow(i) = max(0., snow(i) - fq_fonte) bil_eau_s(i) = bil_eau_s(i) + fq_fonte tsurf_new(i) = tsurf_new(i) - fq_fonte * chasno @@ -96,7 +96,7 @@ !IM cf. JLD/ GKtest fonte aussi pour la glace IF (nisurf == is_sic .OR. nisurf == is_lic) THEN fq_fonte = MAX((tsurf_new(i) - RTT) / chaice, 0.) - ffonte(i) = ffonte(i) + fq_fonte * RLMLT / dtime + ffonte(i) = ffonte(i) + fq_fonte * RLMLT / dtphys bil_eau_s(i) = bil_eau_s(i) + fq_fonte tsurf_new(i) = RTT ENDIF @@ -105,21 +105,17 @@ endif ! S'il y a une hauteur trop importante de neige, elle s'\'ecoule - fqcalving(i) = max(0., snow(i) - snow_max) / dtime + fqcalving(i) = max(0., snow(i) - snow_max) / dtphys snow(i) = min(snow(i), snow_max) enddo IF (nisurf == is_ter) then qsol = MIN(qsol + bil_eau_s, max_eau_sol) else if (nisurf == is_lic) then - if (.not. allocated(run_off_lic)) allocate(run_off_lic(knon)) - ! assumes that the fraction of land-ice does not change during the run - do i = 1, knon - run_off_lic(i) = (coeff_rel * fqcalving(i)) + & + run_off_lic_0(i) = (coeff_rel * fqcalving(i)) + & (1. - coeff_rel) * run_off_lic_0(i) - run_off_lic_0(i) = run_off_lic(i) - run_off_lic(i) = run_off_lic(i) + bil_eau_s(i) / dtime + run_off_lic(i) = run_off_lic_0(i) + bil_eau_s(i) / dtphys enddo endif