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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 202 - (hide annotations)
Wed Jun 8 12:23:41 2016 UTC (7 years, 11 months ago) by guez
File size: 5986 byte(s)
Promoted lmt_pas from local variable of physiq to variable of module
conf_gcm_m.

Removed variable run_off of module interface_surf. Was not
used. Called run_off_ter in LMDZ, but not used nor printed there
either.

Simplified logic in interfoce_lim. The way it was convoluted with
interfsurf_hq and clmain was quite a mess. Extracted reading of SST
into a separate procedure: read_sst. We do not need SST and pctsrf_new
at the same time: SST is not needed for sea-ice surface. I did not
like this programming: going through the procedure repeatedly for
different purposes and testing inside whether there was something to
do or it was already done. Reading is now only controlled by itap and
lmt_pas, instead of debut, jour, jour_lu and deja_lu. Now we do not
copy from pct_tmp to pctsrf_new every time step.

Simplified processing of pctsrf in clmain and below. It was quite
troubling: pctsrf_new was intent out in interfoce_lim but only defined
for ocean and sea-ice. Also the idea of having arrays for all
surfaces, pcsrf and pctsrf_new, in interfsurf_hq, which is called for
a particular surface, was troubling. pctsrf_new for all surfaces was
intent out in intefsurf_hq, but not defined for all surfaces at each
call. Removed argument pctsrf_new of clmain: was a duplicate of pctsrf
on output, and not used in physiq. Replaced pctsrf_new in clmain by
pctsrf_new_oce and pctsrf_new_sic, which were the only ones modified.

1 guez 54 module fonte_neige_m
2    
3     implicit none
4    
5     contains
6    
7 guez 104 SUBROUTINE fonte_neige(nisurf, dtime, tsurf, p1lay, beta, coef1lay, ps, &
8     precip_rain, precip_snow, snow, qsol, t1lay, q1lay, u1lay, v1lay, &
9     petAcoef, peqAcoef, petBcoef, peqBcoef, tsurf_new, evap, fqcalving, &
10     ffonte, run_off_lic_0)
11 guez 54
12     ! Routine de traitement de la fonte de la neige dans le cas du traitement
13 guez 178 ! de sol simplifi\'e
14 guez 54
15 guez 202 ! Laurent Fairhead, March, 2001
16 guez 101
17 guez 178 USE fcttre, ONLY: foeew, qsatl, qsats, thermcep
18 guez 101 USE indicesol, ONLY: epsfra, is_lic, is_sic, is_ter
19 guez 202 USE interface_surf, ONLY: run_off_lic, tau_calv
20 guez 104 use nr_util, only: assert_eq
21 guez 178 USE suphec_m, ONLY: rcpd, rday, retv, rlmlt, rlstt, rlvtt, rtt
22 guez 101 USE yoethf_m, ONLY: r2es, r5ies, r5les, rvtmp2
23    
24 guez 178 integer, intent(IN):: nisurf ! surface \`a traiter
25 guez 101 real, intent(IN):: dtime ! pas de temps de la physique (en s)
26 guez 202 real, intent(IN):: tsurf(:) ! (knon) temperature de surface
27     real, intent(IN):: p1lay(:) ! (knon) pression 1er niveau (milieu de couche)
28     real, intent(IN):: beta(:) ! (knon) evap reelle
29     real, intent(IN):: coef1lay(:) ! (knon) coefficient d'echange
30     real, intent(IN):: ps(:) ! (knon) pression au sol
31 guez 101
32     real, intent(IN):: precip_rain(:) ! (knon)
33     ! precipitation, liquid water mass flux (kg/m2/s), positive down
34    
35 guez 104 real, intent(IN):: precip_snow(:) ! (knon)
36 guez 101 ! precipitation, solid water mass flux (kg/m2/s), positive down
37    
38 guez 104 real, intent(INOUT):: snow(:) ! (knon)
39     ! column-density of mass of snow, in kg m-2
40 guez 101
41     real, intent(INOUT):: qsol(:) ! (knon)
42     ! column-density of water in soil, in kg m-2
43    
44 guez 202 real, intent(IN):: t1lay(:) ! (knon)
45     real, intent(IN):: q1lay(:) ! (knon)
46     real, intent(IN):: u1lay(:), v1lay(:) ! (knon)
47 guez 54
48 guez 202 real, intent(IN):: petAcoef(:), peqAcoef(:) ! (knon)
49     ! coefficients A de la r\'esolution de la couche limite pour t et q
50    
51     real, intent(IN):: petBcoef(:), peqBcoef(:) ! (knon)
52     ! coefficients B de la r\'esolution de la couche limite pour t et q
53    
54 guez 104 real, intent(INOUT):: tsurf_new(:)
55 guez 54 ! tsurf_new temperature au sol
56    
57 guez 104 real, intent(IN):: evap(:) ! (knon)
58    
59 guez 202 real, intent(OUT):: fqcalving(:) ! (knon)
60     ! flux d'eau "perdue" par la surface et n\'ecessaire pour limiter la
61 guez 101 ! hauteur de neige, en kg/m2/s
62 guez 54
63 guez 104 real, intent(OUT):: ffonte(:) ! (knon)
64 guez 202 ! flux thermique utilis\'é pour fondre la neige
65 guez 101
66 guez 202 real, intent(INOUT):: run_off_lic_0(:) ! (knon)
67     ! run off glacier du pas de temps pr\'ecedent
68 guez 101
69     ! Local:
70    
71 guez 178 integer knon ! nombre de points \`a traiter
72 guez 101 real, parameter:: snow_max=3000.
73 guez 54 ! Masse maximum de neige (kg/m2). Au dessus de ce seuil, la neige
74     ! en exces "s'ecoule" (calving)
75    
76 guez 101 integer i
77 guez 103 logical zdelta
78 guez 178 real zcvm5, zx_qs, zcor
79 guez 101 real fq_fonte
80 guez 104 REAL bil_eau_s(size(ps)) ! in kg m-2
81     real snow_evap(size(ps)) ! in kg m-2 s-1
82 guez 188 real, parameter:: t_coup = 273.15
83 guez 101 REAL, parameter:: chasno = 3.334E5/(2.3867E6*0.15)
84     REAL, parameter:: chaice = 3.334E5/(2.3867E6*0.15)
85     real, parameter:: max_eau_sol = 150. ! in kg m-2
86     real coeff_rel
87 guez 54
88 guez 101 !--------------------------------------------------------------------
89 guez 54
90 guez 104 knon = assert_eq((/size(tsurf), size(p1lay), size(beta), size(coef1lay), &
91     size(ps), size(precip_rain), size(precip_snow), size(snow), &
92     size(qsol), size(t1lay), size(q1lay), size(u1lay), size(v1lay), &
93     size(petAcoef), size(peqAcoef), size(petBcoef), size(peqBcoef), &
94     size(tsurf_new), size(evap), size(fqcalving), size(ffonte), &
95     size(run_off_lic_0)/), "fonte_neige knon")
96    
97 guez 54 ! Initialisations
98     coeff_rel = dtime/(tau_calv * rday)
99     bil_eau_s = 0.
100     DO i = 1, knon
101     IF (thermcep) THEN
102 guez 103 zdelta= rtt >= tsurf(i)
103     zcvm5 = merge(R5IES*RLSTT, R5LES*RLVTT, zdelta)
104 guez 101 zcvm5 = zcvm5 / RCPD / (1. + RVTMP2*q1lay(i))
105 guez 54 zx_qs= r2es * FOEEW(tsurf(i), zdelta)/ps(i)
106     zx_qs=MIN(0.5, zx_qs)
107     zcor=1./(1.-retv*zx_qs)
108     zx_qs=zx_qs*zcor
109     ELSE
110 guez 101 IF (tsurf(i) < t_coup) THEN
111 guez 54 zx_qs = qsats(tsurf(i)) / ps(i)
112     ELSE
113     zx_qs = qsatl(tsurf(i)) / ps(i)
114     ENDIF
115     ENDIF
116     ENDDO
117    
118 guez 101 ! Calcul de la temperature de surface
119 guez 54
120 guez 101 WHERE (precip_snow > 0.) snow = snow + precip_snow * dtime
121    
122     WHERE (evap > 0.)
123 guez 104 snow_evap = MIN(snow / dtime, evap)
124 guez 54 snow = snow - snow_evap * dtime
125 guez 101 snow = MAX(0., snow)
126     elsewhere
127     snow_evap = 0.
128 guez 54 end where
129    
130 guez 101 bil_eau_s = precip_rain * dtime - (evap(:knon) - snow_evap(:knon)) * dtime
131 guez 54
132 guez 202 ! Y a-t-il fonte de neige ?
133 guez 54
134     ffonte=0.
135     do i = 1, knon
136 guez 101 if ((snow(i) > epsfra .OR. nisurf == is_sic &
137     .OR. nisurf == is_lic) .AND. tsurf_new(i) >= RTT) then
138     fq_fonte = MIN(MAX((tsurf_new(i)-RTT)/chasno, 0.), snow(i))
139 guez 54 ffonte(i) = fq_fonte * RLMLT/dtime
140     snow(i) = max(0., snow(i) - fq_fonte)
141     bil_eau_s(i) = bil_eau_s(i) + fq_fonte
142     tsurf_new(i) = tsurf_new(i) - fq_fonte * chasno
143     !IM cf JLD/ GKtest fonte aussi pour la glace
144 guez 101 IF (nisurf == is_sic .OR. nisurf == is_lic) THEN
145     fq_fonte = MAX((tsurf_new(i)-RTT)/chaice, 0.)
146 guez 54 ffonte(i) = ffonte(i) + fq_fonte * RLMLT/dtime
147     bil_eau_s(i) = bil_eau_s(i) + fq_fonte
148     tsurf_new(i) = RTT
149     ENDIF
150     endif
151    
152 guez 178 ! S'il y a une hauteur trop importante de neige, elle s'\'ecoule
153 guez 54 fqcalving(i) = max(0., snow(i) - snow_max)/dtime
154     snow(i)=min(snow(i), snow_max)
155    
156     IF (nisurf == is_ter) then
157     qsol(i) = qsol(i) + bil_eau_s(i)
158     qsol(i) = MIN(qsol(i), max_eau_sol)
159     else if (nisurf == is_lic) then
160     run_off_lic(i) = (coeff_rel * fqcalving(i)) + &
161     (1. - coeff_rel) * run_off_lic_0(i)
162     run_off_lic_0(i) = run_off_lic(i)
163     run_off_lic(i) = run_off_lic(i) + bil_eau_s(i)/dtime
164     endif
165     enddo
166    
167     END SUBROUTINE fonte_neige
168    
169     end module fonte_neige_m

  ViewVC Help
Powered by ViewVC 1.1.21