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

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

Parent Directory Parent Directory | Revision Log Revision Log


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

  ViewVC Help
Powered by ViewVC 1.1.21