/[lmdze]/trunk/phylmd/Interface_surf/fonte_neige.f90
ViewVC logotype

Diff of /trunk/phylmd/Interface_surf/fonte_neige.f90

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

trunk/Sources/phylmd/Interface_surf/fonte_neige.f revision 215 by guez, Tue Mar 28 12:46:28 2017 UTC trunk/phylmd/Interface_surf/fonte_neige.f revision 297 by guez, Thu Jul 26 16:02:11 2018 UTC
# Line 12  contains Line 12  contains
12    
13      ! Laurent Fairhead, March, 2001      ! Laurent Fairhead, March, 2001
14    
     USE fcttre, ONLY: foeew, qsatl, qsats  
15      USE indicesol, ONLY: epsfra, is_lic, is_sic, is_ter      USE indicesol, ONLY: epsfra, is_lic, is_sic, is_ter
16      USE interface_surf, ONLY: run_off_lic, tau_calv      USE conf_interface_m, ONLY: tau_calv
17      use nr_util, only: assert_eq      use nr_util, only: assert_eq
18      USE suphec_m, ONLY: rday, rlmlt, rtt      USE suphec_m, ONLY: rday, rlmlt, rtt
19    
# Line 61  contains Line 60  contains
60      REAL, parameter:: chaice = 3.334E5 / (2.3867E6 * 0.15)      REAL, parameter:: chaice = 3.334E5 / (2.3867E6 * 0.15)
61      real, parameter:: max_eau_sol = 150. ! in kg m-2      real, parameter:: max_eau_sol = 150. ! in kg m-2
62      real coeff_rel      real coeff_rel
63        REAL, ALLOCATABLE, SAVE:: run_off_lic(:) ! ruissellement total
64    
65      !--------------------------------------------------------------------      !--------------------------------------------------------------------
66    
# Line 79  contains Line 79  contains
79         snow_evap = 0.         snow_evap = 0.
80      end where      end where
81    
82      bil_eau_s = precip_rain * dtime - (evap - snow_evap) * dtime      bil_eau_s = (precip_rain - evap + snow_evap) * dtime
83    
84      ! Y a-t-il fonte de neige ?      ! Y a-t-il fonte de neige ?
85    
# Line 91  contains Line 91  contains
91            snow(i) = max(0., snow(i) - fq_fonte)            snow(i) = max(0., snow(i) - fq_fonte)
92            bil_eau_s(i) = bil_eau_s(i) + fq_fonte            bil_eau_s(i) = bil_eau_s(i) + fq_fonte
93            tsurf_new(i) = tsurf_new(i) - fq_fonte * chasno            tsurf_new(i) = tsurf_new(i) - fq_fonte * chasno
94              
95            !IM cf. JLD/ GKtest fonte aussi pour la glace            !IM cf. JLD/ GKtest fonte aussi pour la glace
96            IF (nisurf == is_sic .OR. nisurf == is_lic) THEN            IF (nisurf == is_sic .OR. nisurf == is_lic) THEN
97               fq_fonte = MAX((tsurf_new(i) - RTT) / chaice, 0.)               fq_fonte = MAX((tsurf_new(i) - RTT) / chaice, 0.)
# Line 106  contains Line 106  contains
106         ! S'il y a une hauteur trop importante de neige, elle s'\'ecoule         ! S'il y a une hauteur trop importante de neige, elle s'\'ecoule
107         fqcalving(i) = max(0., snow(i) - snow_max) / dtime         fqcalving(i) = max(0., snow(i) - snow_max) / dtime
108         snow(i) = min(snow(i), snow_max)         snow(i) = min(snow(i), snow_max)
109        enddo
110    
111        IF (nisurf == is_ter) then
112           qsol = MIN(qsol + bil_eau_s, max_eau_sol)
113        else if (nisurf == is_lic) then
114           if (.not. allocated(run_off_lic)) allocate(run_off_lic(knon))
115           ! assumes that the fraction of land-ice does not change during the run
116    
117         IF (nisurf == is_ter) then         do i = 1, knon
           qsol(i) = qsol(i) + bil_eau_s(i)  
           qsol(i) = MIN(qsol(i), max_eau_sol)  
        else if (nisurf == is_lic) then  
118            run_off_lic(i) = (coeff_rel * fqcalving(i)) + &            run_off_lic(i) = (coeff_rel * fqcalving(i)) + &
119                 (1. - coeff_rel) * run_off_lic_0(i)                 (1. - coeff_rel) * run_off_lic_0(i)
120            run_off_lic_0(i) = run_off_lic(i)            run_off_lic_0(i) = run_off_lic(i)
121            run_off_lic(i) = run_off_lic(i) + bil_eau_s(i) / dtime            run_off_lic(i) = run_off_lic(i) + bil_eau_s(i) / dtime
122         endif         enddo
123      enddo      endif
124    
125    END SUBROUTINE fonte_neige    END SUBROUTINE fonte_neige
126    

Legend:
Removed from v.215  
changed lines
  Added in v.297

  ViewVC Help
Powered by ViewVC 1.1.21