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

Annotation of /trunk/phylmd/Interface_surf/fonte_neige.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 301 - (hide annotations)
Thu Aug 2 17:23:07 2018 UTC (5 years, 10 months ago) by guez
File size: 4168 byte(s)
Move the call to conf_interface up to physiq, so there is no need to
test first call inside pbl_surface for this.

run_off_lic in fonte_neige was computed but not used. Pass it up to
pbl_surface so we can output it (following LMDZ).

Simplify the logic in interfsur_lim so we do not need debut.

Remove the tests on the order of surface types in interfsurf_hq. Just
add comments in indicesol.

1 guez 54 module fonte_neige_m
2    
3     implicit none
4    
5     contains
6    
7 guez 299 SUBROUTINE fonte_neige(nisurf, precip_rain, precip_snow, snow, qsol, &
8 guez 301 tsurf_new, evap, fqcalving, ffonte, run_off_lic_0, run_off_lic)
9 guez 54
10     ! Routine de traitement de la fonte de la neige dans le cas du traitement
11 guez 178 ! de sol simplifi\'e
12 guez 54
13 guez 202 ! Laurent Fairhead, March, 2001
14 guez 101
15 guez 299 use comconst, only: dtphys
16 guez 101 USE indicesol, ONLY: epsfra, is_lic, is_sic, is_ter
17 guez 297 USE conf_interface_m, ONLY: tau_calv
18 guez 104 use nr_util, only: assert_eq
19 guez 215 USE suphec_m, ONLY: rday, rlmlt, rtt
20 guez 101
21 guez 178 integer, intent(IN):: nisurf ! surface \`a traiter
22 guez 101
23     real, intent(IN):: precip_rain(:) ! (knon)
24 guez 206 ! precipitation, liquid water mass flux (kg / m2 / s), positive down
25 guez 101
26 guez 104 real, intent(IN):: precip_snow(:) ! (knon)
27 guez 206 ! precipitation, solid water mass flux (kg / m2 / s), positive down
28 guez 101
29 guez 104 real, intent(INOUT):: snow(:) ! (knon)
30     ! column-density of mass of snow, in kg m-2
31 guez 101
32     real, intent(INOUT):: qsol(:) ! (knon)
33     ! column-density of water in soil, in kg m-2
34    
35 guez 207 real, intent(INOUT):: tsurf_new(:) ! (knon) temp\'erature au sol
36 guez 104 real, intent(IN):: evap(:) ! (knon)
37    
38 guez 202 real, intent(OUT):: fqcalving(:) ! (knon)
39     ! flux d'eau "perdue" par la surface et n\'ecessaire pour limiter la
40 guez 206 ! hauteur de neige, en kg / m2 / s
41 guez 54
42 guez 104 real, intent(OUT):: ffonte(:) ! (knon)
43 guez 202 ! flux thermique utilis\'é pour fondre la neige
44 guez 101
45 guez 202 real, intent(INOUT):: run_off_lic_0(:) ! (knon)
46     ! run off glacier du pas de temps pr\'ecedent
47 guez 101
48 guez 301 REAL, intent(OUT):: run_off_lic(:) ! (knon) ruissellement total
49    
50 guez 101 ! Local:
51    
52 guez 178 integer knon ! nombre de points \`a traiter
53 guez 101 real, parameter:: snow_max=3000.
54 guez 206 ! Masse maximum de neige (kg / m2). Au dessus de ce seuil, la neige
55 guez 215 ! en exces "s'\'ecoule" (calving).
56 guez 54
57 guez 101 integer i
58     real fq_fonte
59 guez 215 REAL bil_eau_s(size(precip_rain)) ! (knon) in kg m-2
60     real snow_evap(size(precip_rain)) ! (knon) in kg m-2 s-1
61     REAL, parameter:: chasno = 3.334E5 / (2.3867E6 * 0.15)
62     REAL, parameter:: chaice = 3.334E5 / (2.3867E6 * 0.15)
63 guez 101 real, parameter:: max_eau_sol = 150. ! in kg m-2
64     real coeff_rel
65 guez 54
66 guez 101 !--------------------------------------------------------------------
67 guez 54
68 guez 215 knon = assert_eq((/size(precip_rain), size(precip_snow), size(snow), &
69     size(qsol), size(tsurf_new), size(evap), size(fqcalving), &
70     size(ffonte), size(run_off_lic_0)/), "fonte_neige knon")
71 guez 104
72 guez 299 coeff_rel = dtphys / (tau_calv * rday)
73     WHERE (precip_snow > 0.) snow = snow + precip_snow * dtphys
74 guez 101
75     WHERE (evap > 0.)
76 guez 299 snow_evap = MIN(snow / dtphys, evap)
77     snow = snow - snow_evap * dtphys
78 guez 101 snow = MAX(0., snow)
79     elsewhere
80     snow_evap = 0.
81 guez 54 end where
82    
83 guez 299 bil_eau_s = (precip_rain - evap + snow_evap) * dtphys
84 guez 54
85 guez 202 ! Y a-t-il fonte de neige ?
86 guez 54
87     do i = 1, knon
88 guez 101 if ((snow(i) > epsfra .OR. nisurf == is_sic &
89     .OR. nisurf == is_lic) .AND. tsurf_new(i) >= RTT) then
90 guez 207 fq_fonte = MIN(MAX((tsurf_new(i) - RTT) / chasno, 0.), snow(i))
91 guez 299 ffonte(i) = fq_fonte * RLMLT / dtphys
92 guez 54 snow(i) = max(0., snow(i) - fq_fonte)
93     bil_eau_s(i) = bil_eau_s(i) + fq_fonte
94     tsurf_new(i) = tsurf_new(i) - fq_fonte * chasno
95 guez 217
96 guez 215 !IM cf. JLD/ GKtest fonte aussi pour la glace
97 guez 101 IF (nisurf == is_sic .OR. nisurf == is_lic) THEN
98 guez 207 fq_fonte = MAX((tsurf_new(i) - RTT) / chaice, 0.)
99 guez 299 ffonte(i) = ffonte(i) + fq_fonte * RLMLT / dtphys
100 guez 54 bil_eau_s(i) = bil_eau_s(i) + fq_fonte
101     tsurf_new(i) = RTT
102     ENDIF
103 guez 215 else
104     ffonte(i) = 0.
105 guez 54 endif
106    
107 guez 178 ! S'il y a une hauteur trop importante de neige, elle s'\'ecoule
108 guez 299 fqcalving(i) = max(0., snow(i) - snow_max) / dtphys
109 guez 215 snow(i) = min(snow(i), snow_max)
110 guez 217 enddo
111 guez 54
112 guez 217 IF (nisurf == is_ter) then
113     qsol = MIN(qsol + bil_eau_s, max_eau_sol)
114     else if (nisurf == is_lic) then
115     do i = 1, knon
116 guez 300 run_off_lic_0(i) = (coeff_rel * fqcalving(i)) + &
117 guez 54 (1. - coeff_rel) * run_off_lic_0(i)
118 guez 300 run_off_lic(i) = run_off_lic_0(i) + bil_eau_s(i) / dtphys
119 guez 217 enddo
120     endif
121 guez 54
122     END SUBROUTINE fonte_neige
123    
124     end module fonte_neige_m

  ViewVC Help
Powered by ViewVC 1.1.21