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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 305 - (show annotations)
Tue Sep 11 11:08:38 2018 UTC (5 years, 8 months ago) by guez
File size: 8215 byte(s)
We want to keep the same variable names throughout procedures. In
pbl_surface, rain_fall and snow_fall were passed to clqh and became
precip_rain and precip_snow. Which name should we choose?
Precipitation normally refers to water in all phases. Rainfall and
snowfall seem to be more common names to distinguish liquid water and
snow. Cf. CF standard names. So change everywhere precip_rain to
rain_fall and precip_snow to snow_fall.

1 module interfsurf_hq_m
2
3 implicit none
4
5 contains
6
7 SUBROUTINE interfsurf_hq(julien, mu0, nisurf, knindex, tsoil, qsol, u1_lay, &
8 v1_lay, temp_air, spechum, tq_cdrag, tAcoef, qAcoef, tBcoef, qBcoef, &
9 rain_fall, snow_fall, rugos, rugoro, snow, qsurf, ts, p1lay, ps, &
10 radsol, evap, flux_t, fluxlat, dflux_l, dflux_s, tsurf_new, albedo, &
11 z0_new, pctsrf_new_sic, agesno, fqcalving, ffonte, run_off_lic_0, &
12 run_off_lic)
13
14 ! Cette routine sert d'aiguillage entre l'atmosph\`ere et la surface
15 ! en g\'en\'eral (sols continentaux, oc\'eans, glaces) pour les flux de
16 ! chaleur et d'humidit\'e.
17
18 ! Laurent Fairhead, February 2000
19
20 USE abort_gcm_m, ONLY: abort_gcm
21 use alboc_cd_m, only: alboc_cd
22 USE albsno_m, ONLY: albsno
23 USE calcul_fluxs_m, ONLY: calcul_fluxs
24 USE fonte_neige_m, ONLY: fonte_neige
25 USE indicesol, ONLY: epsfra, is_lic, is_oce, is_sic, is_ter
26 USE interfsur_lim_m, ONLY: interfsur_lim
27 use limit_read_sst_m, only: limit_read_sst
28 use soil_m, only: soil
29 USE suphec_m, ONLY: rcpd, rtt
30
31 integer, intent(IN):: julien ! jour dans l'annee en cours
32 real, intent(IN):: mu0(:) ! (knon) cosinus de l'angle solaire zenithal
33 integer, intent(IN):: nisurf ! index de la surface a traiter
34
35 integer, intent(in):: knindex(:) ! (knon)
36 ! index des points de la surface a traiter
37
38 REAL, intent(inout):: tsoil(:, :) ! (knon, nsoilmx)
39
40 REAL, intent(INOUT):: qsol(:) ! (knon)
41 ! column-density of water in soil, in kg m-2
42
43 real, intent(IN):: u1_lay(:), v1_lay(:) ! (knon) vitesse 1ere couche
44
45 real, intent(IN):: temp_air(:) ! (knon) temperature de l'air 1ere couche
46 real, intent(IN):: spechum(:) ! (knon) humidite specifique 1ere couche
47 real, intent(IN):: tq_cdrag(:) ! (knon) coefficient d'echange
48
49 real, intent(IN):: tAcoef(:), qAcoef(:) ! (knon)
50 ! coefficients A de la r\'esolution de la couche limite pour t et q
51
52 real, intent(IN):: tBcoef(:), qBcoef(:) ! (knon)
53 ! coefficients B de la r\'esolution de la couche limite pour t et q
54
55 real, intent(IN):: rain_fall(:) ! (knon)
56 ! precipitation, liquid water mass flux (kg / m2 / s), positive down
57
58 real, intent(IN):: snow_fall(:) ! (knon)
59 ! precipitation, solid water mass flux (kg / m2 / s), positive down
60
61 real, intent(IN):: rugos(:) ! (knon) rugosite
62 real, intent(IN):: rugoro(:) ! (knon) rugosite orographique
63 real, intent(INOUT):: snow(:) ! (knon)
64 real, intent(OUT):: qsurf(:) ! (knon)
65 real, intent(IN):: ts(:) ! (knon) temp\'erature de surface
66 real, intent(IN):: p1lay(:) ! (knon) pression 1er niveau (milieu de couche)
67 real, intent(IN):: ps(:) ! (knon) pression au sol
68 REAL, INTENT(IN):: radsol(:) ! (knon) rayonnement net au sol (LW + SW)
69 real, intent(OUT):: evap(:) ! (knon) evaporation totale
70
71 real, intent(OUT):: flux_t(:) ! (knon) flux de chaleur sensible
72 ! (Cp T) à la surface, positif vers le bas, W / m2
73
74 real, intent(OUT):: fluxlat(:) ! (knon) flux de chaleur latente
75 real, intent(OUT):: dflux_l(:), dflux_s(:) ! (knon)
76 real, intent(OUT):: tsurf_new(:) ! (knon) temp\'erature au sol
77 real, intent(OUT):: albedo(:) ! (knon) albedo
78 real, intent(OUT):: z0_new(:) ! (knon) surface roughness
79
80 real, intent(in):: pctsrf_new_sic(:) ! (knon)
81 ! nouvelle repartition des surfaces
82
83 real, intent(INOUT):: agesno(:) ! (knon)
84
85 real, intent(OUT):: fqcalving(:) ! (knon)
86 ! Flux d'eau "perdue" par la surface et n\'ecessaire pour limiter la
87 ! hauteur de neige, en kg / m2 / s
88
89 real, intent(OUT):: ffonte(:) ! (knon)
90 ! flux thermique utilis\'e pour fondre la neige
91
92 real, intent(INOUT):: run_off_lic_0(:) ! (knon)
93 ! run_off_lic_0 runoff glacier du pas de temps precedent
94
95 REAL, intent(OUT):: run_off_lic(:) ! (knon) ruissellement total
96
97 ! Local:
98 REAL soilcap(size(knindex)) ! (knon)
99 REAL soilflux(size(knindex)) ! (knon)
100 integer ii
101 real cal(size(knindex)) ! (knon)
102 real beta(size(knindex)) ! (knon) evap reelle
103 real tsurf(size(knindex)) ! (knon)
104 real alb_neig(size(knindex)) ! (knon)
105 real zfra(size(knindex)) ! (knon)
106 REAL, PARAMETER:: fmagic = 1. ! facteur magique pour r\'egler l'alb\'edo
107 REAL, PARAMETER:: max_eau_sol = 150. ! in kg m-2
108 REAL, PARAMETER:: tau_gl = 86400. * 5.
109
110 !-------------------------------------------------------------
111
112 select case (nisurf)
113 case (is_ter)
114 ! Surface "terre", appel \`a l'interface avec les sols continentaux
115
116 ! Calcul age de la neige
117
118 ! Read albedo from the file containing boundary conditions then
119 ! add the albedo of snow:
120
121 call interfsur_lim(julien, knindex, albedo, z0_new)
122
123 beta = min(2. * qsol / max_eau_sol, 1.)
124 CALL soil(is_ter, snow, ts, tsoil, soilcap, soilflux)
125 cal = RCPD / soilcap
126
127 CALL calcul_fluxs(ts, p1lay, cal, beta, tq_cdrag, ps, qsurf, &
128 radsol + soilflux, temp_air, spechum, u1_lay, v1_lay, tAcoef, &
129 qAcoef, tBcoef, qBcoef, tsurf_new, evap, fluxlat, flux_t, dflux_s, &
130 dflux_l, dif_grnd = 0.)
131 CALL fonte_neige(is_ter, rain_fall, snow_fall, snow, qsol, &
132 tsurf_new, evap, fqcalving, ffonte, run_off_lic_0, run_off_lic)
133
134 call albsno(agesno, alb_neig, snow_fall)
135 where (snow < 0.0001) agesno = 0.
136 zfra = max(0., min(1., snow / (snow + 10.)))
137 albedo = alb_neig * zfra + albedo * (1. - zfra)
138 z0_new = sqrt(z0_new**2 + rugoro**2)
139 case (is_oce)
140 ! Surface "oc\'ean", appel \`a l'interface avec l'oc\'ean
141
142 ffonte = 0.
143 call limit_read_sst(julien, knindex, tsurf)
144 cal = 0.
145 beta = 1.
146 call calcul_fluxs(tsurf, p1lay, cal, beta, tq_cdrag, ps, qsurf, radsol, &
147 temp_air, spechum, u1_lay, v1_lay, tAcoef, qAcoef, tBcoef, qBcoef, &
148 tsurf_new, evap, fluxlat, flux_t, dflux_s, dflux_l, dif_grnd = 0.)
149 agesno = 0.
150 albedo = alboc_cd(mu0) * fmagic
151 z0_new = sqrt(rugos**2 + rugoro**2)
152 fqcalving = 0.
153 case (is_sic)
154 ! Surface "glace de mer" appel a l'interface avec l'ocean
155
156 DO ii = 1, size(knindex)
157 IF (pctsrf_new_sic(ii) < EPSFRA) then
158 snow(ii) = 0.
159 tsurf_new(ii) = RTT - 1.8
160 tsoil(ii, :) = RTT - 1.8
161 else
162 tsurf_new(ii) = ts(ii)
163 endif
164 enddo
165
166 CALL soil(is_sic, snow, tsurf_new, tsoil, soilcap, soilflux)
167 cal = RCPD / soilcap
168 tsurf = tsurf_new
169 beta = 1.
170 CALL calcul_fluxs(tsurf, p1lay, cal, beta, tq_cdrag, ps, qsurf, &
171 radsol + soilflux, temp_air, spechum, u1_lay, v1_lay, tAcoef, &
172 qAcoef, tBcoef, qBcoef, tsurf_new, evap, fluxlat, flux_t, dflux_s, &
173 dflux_l, dif_grnd = 1. / tau_gl)
174 CALL fonte_neige(is_sic, rain_fall, snow_fall, snow, qsol, &
175 tsurf_new, evap, fqcalving, ffonte, run_off_lic_0, run_off_lic)
176
177 ! Compute the albedo:
178
179 CALL albsno(agesno, alb_neig, snow_fall)
180 WHERE (snow < 0.0001) agesno = 0.
181 zfra = MAX(0., MIN(1., snow / (snow + 10.)))
182 albedo = alb_neig * zfra + 0.6 * (1. - zfra)
183
184 z0_new = SQRT(0.002**2 + rugoro**2)
185 case (is_lic)
186 ! Surface "glacier continentaux" appel a l'interface avec le sol
187
188 CALL soil(is_lic, snow, ts, tsoil, soilcap, soilflux)
189 cal = RCPD / soilcap
190 beta = 1.
191 call calcul_fluxs(ts, p1lay, cal, beta, tq_cdrag, ps, qsurf, &
192 radsol + soilflux, temp_air, spechum, u1_lay, v1_lay, tAcoef, &
193 qAcoef, tBcoef, qBcoef, tsurf_new, evap, fluxlat, flux_t, dflux_s, &
194 dflux_l, dif_grnd = 0.)
195 call fonte_neige(is_lic, rain_fall, snow_fall, snow, qsol, &
196 tsurf_new, evap, fqcalving, ffonte, run_off_lic_0, run_off_lic)
197
198 ! calcul albedo
199 CALL albsno(agesno, alb_neig, snow_fall)
200 WHERE (snow < 0.0001) agesno = 0.
201 albedo = 0.77
202
203 ! Rugosite
204 z0_new = rugoro
205 case default
206 print *, 'Index surface = ', nisurf
207 call abort_gcm("interfsurf_hq", 'Index surface non valable')
208 end select
209
210 END SUBROUTINE interfsurf_hq
211
212 end module interfsurf_hq_m

  ViewVC Help
Powered by ViewVC 1.1.21