/[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 217 - (show annotations)
Thu Mar 30 14:25:18 2017 UTC (7 years, 2 months ago) by guez
Original Path: trunk/Sources/phylmd/Interface_surf/fonte_neige.f
File size: 4414 byte(s)
run_off_lic downgraded from variable of module interface_surf to local
variable of fonte_neige.

Code could not work with ok_aie set to true, so removed this
possibility. tauae, piz_ae, cg_ae, topswai, solswai were then
0. cldtaupi was the same as cldtaupd.

In sw and procedures called by sw, flag_aer did not need to be double
precision, changed it to logical.

Downgraded re and fl from arguments of newmicro to local
variables. Added output of re and fl (following 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: 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 REAL, ALLOCATABLE, SAVE:: run_off_lic(:) ! ruissellement total
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 = dtime / (tau_calv * rday)
73 WHERE (precip_snow > 0.) snow = snow + precip_snow * dtime
74
75 WHERE (evap > 0.)
76 snow_evap = MIN(snow / dtime, evap)
77 snow = snow - snow_evap * dtime
78 snow = MAX(0., snow)
79 elsewhere
80 snow_evap = 0.
81 end where
82
83 bil_eau_s = (precip_rain - evap + snow_evap) * dtime
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 / dtime
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 / dtime
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) / dtime
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 if (.not. allocated(run_off_lic)) allocate(run_off_lic(knon))
116 ! assumes that the fraction of land-ice does not change during the run
117
118 do i = 1, knon
119 run_off_lic(i) = (coeff_rel * fqcalving(i)) + &
120 (1. - coeff_rel) * run_off_lic_0(i)
121 run_off_lic_0(i) = run_off_lic(i)
122 run_off_lic(i) = run_off_lic(i) + bil_eau_s(i) / dtime
123 enddo
124 endif
125
126 END SUBROUTINE fonte_neige
127
128 end module fonte_neige_m

  ViewVC Help
Powered by ViewVC 1.1.21