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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 215 - (show annotations)
Tue Mar 28 12:46:28 2017 UTC (7 years, 2 months ago) by guez
Original Path: trunk/Sources/phylmd/Interface_surf/fonte_neige.f
File size: 4244 byte(s)
size(snow) is now knon in interfsurf_hq.

Renamed snow to fsnow in clmain, same name as corresponding actual
argument. We can then rename ysnow to simply snow in clmain, same name
as corresponding dummy argument of clqh. No need to initialize local
snow to 0 since it is only used with indices 1:knon and already
initialized from fsnow for each type of surface. If there is no point
for a given type of surface, fsnow should be reset to 0 for this
type. We need to give a valid value to fsnow in this case even if it
will be multiplied by pctsrf = 0 in physiq.

In physiq, no need for intermediate zxsnow for output.

Removed unused arguments tsurf, p1lay, beta, coef1lay, ps, t1lay,
q1lay, u1lay, v1lay, petAcoef, peqAcoef, petBcoef, peqBcoef of
fonte_neige, with unused computations of zx_qs and zcor. (Same was
done in LMDZ.)

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

  ViewVC Help
Powered by ViewVC 1.1.21