1 | |
---|
2 | MODULE interface_surf |
---|
3 | |
---|
4 | ! Ce module regroupe toutes les routines gerant l'interface entre le modele |
---|
5 | ! atmospherique et les modeles de surface (sols continentaux, oceans, glaces) |
---|
6 | ! Les routines sont les suivantes: |
---|
7 | ! |
---|
8 | ! interfsurf_*: routines d'aiguillage vers les interfaces avec les |
---|
9 | ! differents modeles de surface |
---|
10 | ! interfsol\ |
---|
11 | ! > routines d'interface proprement dite |
---|
12 | ! interfoce/ |
---|
13 | ! |
---|
14 | ! interfstart: routine d'initialisation et de lecture de l'etat initial |
---|
15 | ! "interface" |
---|
16 | ! interffin : routine d'ecriture de l'etat de redemmarage de l'interface |
---|
17 | ! |
---|
18 | ! |
---|
19 | ! L. Fairhead, LMD, 02/2000 |
---|
20 | |
---|
21 | USE ioipsl |
---|
22 | |
---|
23 | IMPLICIT none |
---|
24 | |
---|
25 | PRIVATE |
---|
26 | PUBLIC :: interfsurf,interfsurf_hq |
---|
27 | |
---|
28 | INTERFACE interfsurf |
---|
29 | module procedure interfsurf_hq, interfsurf_vent |
---|
30 | END INTERFACE |
---|
31 | |
---|
32 | INTERFACE interfoce |
---|
33 | module procedure interfoce_cpl, interfoce_slab, interfoce_lim |
---|
34 | END INTERFACE |
---|
35 | |
---|
36 | #include "YOMCST.inc" |
---|
37 | #include "indicesol.inc" |
---|
38 | |
---|
39 | |
---|
40 | ! run_off ruissellement total |
---|
41 | real, allocatable, dimension(:),save :: run_off |
---|
42 | |
---|
43 | |
---|
44 | CONTAINS |
---|
45 | ! |
---|
46 | !############################################################################ |
---|
47 | ! |
---|
48 | SUBROUTINE interfsurf_hq(itime, dtime, jour, & |
---|
49 | & klon, nisurf, knon, knindex, rlon, rlat, & |
---|
50 | & debut, lafin, ok_veget, & |
---|
51 | & zlev, zlflu, u1_lay, v1_lay, temp_air, spechum, hum_air, ccanopy, & |
---|
52 | & tq_cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, & |
---|
53 | & precip_rain, precip_snow, lwdown, swnet, swdown, & |
---|
54 | & tsurf, p1lay, cal, beta, coef1lay, ps, radsol, dif_grnd, & |
---|
55 | & ocean, & |
---|
56 | & evap, fluxsens, fluxlat, dflux_l, dflux_s, & |
---|
57 | & tsol_rad, tsurf_new, alb_new, emis_new, z0_new, pctsrf_new) |
---|
58 | |
---|
59 | |
---|
60 | ! Cette routine sert d'aiguillage entre l'atmosphere et la surface en general |
---|
61 | ! (sols continentaux, oceans, glaces) pour les fluxs de chaleur et d'humidite. |
---|
62 | ! En pratique l'interface se fait entre la couche limite du modele |
---|
63 | ! atmospherique (clmain.F) et les routines de surface (sechiba, oasis, ...) |
---|
64 | ! |
---|
65 | ! |
---|
66 | ! L.Fairhead 02/2000 |
---|
67 | ! |
---|
68 | ! input: |
---|
69 | ! itime numero du pas de temps |
---|
70 | ! klon nombre total de points de grille |
---|
71 | ! dtime pas de temps de la physique (en s) |
---|
72 | ! jour jour dans l'annee en cours |
---|
73 | ! nisurf index de la surface a traiter (1 = sol continental) |
---|
74 | ! knon nombre de points de la surface a traiter |
---|
75 | ! knindex index des points de la surface a traiter |
---|
76 | ! rlon longitudes |
---|
77 | ! rlat latitudes |
---|
78 | ! debut logical: 1er appel a la physique |
---|
79 | ! lafin logical: dernier appel a la physique |
---|
80 | ! ok_veget logical: appel ou non au schema de surface continental |
---|
81 | ! (si false calcul simplifie des fluxs sur les continents) |
---|
82 | ! zlev hauteur de la premiere couche |
---|
83 | ! zlflu epaisseur de la premier couche |
---|
84 | ! u1_lay vitesse u 1ere couche |
---|
85 | ! v1_lay vitesse v 1ere couche |
---|
86 | ! temp_air temperature de l'air 1ere couche |
---|
87 | ! spechum humidite specifique 1ere couche |
---|
88 | ! hum_air humidite de l'air |
---|
89 | ! ccanopy concentration CO2 canopee |
---|
90 | ! tq_cdrag cdrag |
---|
91 | ! petAcoef coeff. A de la resolution de la CL pour t |
---|
92 | ! peqAcoef coeff. A de la resolution de la CL pour q |
---|
93 | ! petBcoef coeff. B de la resolution de la CL pour t |
---|
94 | ! peqBcoef coeff. B de la resolution de la CL pour q |
---|
95 | ! precip_rain precipitation liquide |
---|
96 | ! precip_snow precipitation solide |
---|
97 | ! lwdown flux IR entrant a la surface |
---|
98 | ! swnet flux solaire net |
---|
99 | ! swdown flux solaire entrant a la surface |
---|
100 | ! tsurf temperature de surface |
---|
101 | ! p1lay pression 1er niveau (milieu de couche) |
---|
102 | ! cal capacite calorifique du sol |
---|
103 | ! beta evap reelle |
---|
104 | ! coef1lay coefficient d'echange |
---|
105 | ! ps pression au sol |
---|
106 | ! radsol rayonnement net aus sol (LW + SW) |
---|
107 | ! dif_grnd coeff. diffusion vers le sol profond |
---|
108 | ! ocean type d'ocean utilise (force, slab, couple) |
---|
109 | ! |
---|
110 | ! output: |
---|
111 | ! evap evaporation totale |
---|
112 | ! fluxsens flux de chaleur sensible |
---|
113 | ! fluxlat flux de chaleur latente |
---|
114 | ! tsol_rad |
---|
115 | ! tsurf_new temperature au sol |
---|
116 | ! alb_new albedo |
---|
117 | ! emis_new emissivite |
---|
118 | ! z0_new surface roughness |
---|
119 | |
---|
120 | |
---|
121 | ! Parametres d'entree |
---|
122 | integer, intent(IN) :: itime |
---|
123 | integer, intent(IN) :: klon |
---|
124 | real, intent(IN) :: dtime |
---|
125 | integer, intent(IN) :: jour |
---|
126 | integer, intent(IN) :: nisurf |
---|
127 | integer, intent(IN) :: knon |
---|
128 | integer, dimension(knon), intent(in) :: knindex |
---|
129 | logical, intent(IN) :: debut, lafin, ok_veget |
---|
130 | real, dimension(klon), intent(IN) :: rlon, rlat |
---|
131 | real, dimension(knon), intent(IN) :: zlev, zlflu |
---|
132 | real, dimension(knon), intent(IN) :: u1_lay, v1_lay |
---|
133 | real, dimension(knon), intent(IN) :: temp_air, spechum |
---|
134 | real, dimension(knon), intent(IN) :: hum_air, ccanopy |
---|
135 | real, dimension(knon), intent(IN) :: tq_cdrag, petAcoef, peqAcoef |
---|
136 | real, dimension(knon), intent(IN) :: petBcoef, peqBcoef |
---|
137 | real, dimension(knon), intent(IN) :: precip_rain, precip_snow |
---|
138 | real, dimension(knon), intent(IN) :: lwdown, swnet, swdown, ps |
---|
139 | real, dimension(knon), intent(IN) :: tsurf, p1lay, cal, beta, coef1lay |
---|
140 | real, dimension(knon), intent(IN) :: radsol, dif_grnd |
---|
141 | character (len = 6) :: ocean |
---|
142 | |
---|
143 | ! Parametres de sortie |
---|
144 | real, dimension(knon), intent(OUT):: evap, fluxsens, fluxlat |
---|
145 | real, dimension(knon), intent(OUT):: tsol_rad, tsurf_new, alb_new |
---|
146 | real, dimension(knon), intent(OUT):: emis_new, z0_new |
---|
147 | real, dimension(knon), intent(OUT):: dflux_l, dflux_s |
---|
148 | real, dimension(klon,nbsrf), intent(OUT) :: pctsrf_new |
---|
149 | |
---|
150 | ! Local |
---|
151 | character (len = 20) :: modname = 'interfsurf_hq' |
---|
152 | character (len = 80) :: abort_message |
---|
153 | logical, save :: first_call = .true. |
---|
154 | integer :: error |
---|
155 | logical :: check = .true. |
---|
156 | |
---|
157 | if (check) write(*,*) 'Entree ', modname |
---|
158 | ! |
---|
159 | ! On doit commencer par appeler les schemas de surfaces continentales |
---|
160 | ! car l'ocean a besoin du ruissellement qui est y calcule |
---|
161 | ! |
---|
162 | if (first_call) then |
---|
163 | if (nisurf /= is_ter .and. klon > 1) then |
---|
164 | write(*,*)' *** Warning ***' |
---|
165 | write(*,*)' nisurf = ',nisurf,' /= is_ter = ',is_ter |
---|
166 | write(*,*)'or on doit commencer par les surfaces continentales' |
---|
167 | abort_message='voir ci-dessus' |
---|
168 | call abort_gcm(modname,abort_message,1) |
---|
169 | endif |
---|
170 | if (ocean /= 'slab ' .and. ocean /= 'force ' .and. ocean /= 'couple') then |
---|
171 | write(*,*)' *** Warning ***' |
---|
172 | write(*,*)'Option couplage pour l''ocean = ', ocean |
---|
173 | abort_message='option pour l''ocean non valable' |
---|
174 | call abort_gcm(modname,abort_message,1) |
---|
175 | endif |
---|
176 | endif |
---|
177 | first_call = .false. |
---|
178 | |
---|
179 | ! Aiguillage vers les differents schemas de surface |
---|
180 | |
---|
181 | if (nisurf == is_ter) then |
---|
182 | ! |
---|
183 | ! Surface "terre" appel a l'interface avec les sols continentaux |
---|
184 | ! |
---|
185 | ! allocation du run-off |
---|
186 | if (.not. allocated(run_off)) then |
---|
187 | allocate(run_off(knon), stat = error) |
---|
188 | if (error /= 0) then |
---|
189 | abort_message='Pb allocation run_off' |
---|
190 | call abort_gcm(modname,abort_message,1) |
---|
191 | endif |
---|
192 | else if (size(run_off) /= knon) then |
---|
193 | write(*,*)'Bizarre, le nombre de points continentaux' |
---|
194 | write(*,*)'a change entre deux appels. Je continue ...' |
---|
195 | deallocate(run_off, stat = error) |
---|
196 | allocate(run_off(knon), stat = error) |
---|
197 | if (error /= 0) then |
---|
198 | abort_message='Pb allocation run_off' |
---|
199 | call abort_gcm(modname,abort_message,1) |
---|
200 | endif |
---|
201 | endif |
---|
202 | ! |
---|
203 | call interfsol(itime, klon, dtime, nisurf, knon, & |
---|
204 | & knindex, rlon, rlat, & |
---|
205 | & debut, lafin, ok_veget, & |
---|
206 | & zlev, zlflu, u1_lay, v1_lay, temp_air, spechum, hum_air, ccanopy, & |
---|
207 | & tq_cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, & |
---|
208 | & precip_rain, precip_snow, lwdown, swnet, swdown, & |
---|
209 | & tsurf, p1lay, cal, beta, coef1lay, ps, radsol, dif_grnd, & |
---|
210 | & evap, fluxsens, fluxlat, & |
---|
211 | & tsol_rad, tsurf_new, alb_new, emis_new, z0_new, dflux_l, dflux_s) |
---|
212 | |
---|
213 | ! |
---|
214 | else if (nisurf == is_oce) then |
---|
215 | |
---|
216 | if (check) write(*,*)'ocean, nisurf = ',nisurf |
---|
217 | ! |
---|
218 | ! Surface "ocean" appel a l'interface avec l'ocean |
---|
219 | ! |
---|
220 | ! if (ocean == 'couple') then |
---|
221 | ! call interfoce(nisurf, ocean) |
---|
222 | ! else if (ocean == 'slab ') then |
---|
223 | ! call interfoce(nisurf) |
---|
224 | ! else ! lecture conditions limites |
---|
225 | ! call interfoce(itime, dtime, jour, & |
---|
226 | ! & klon, nisurf, knon, knindex, & |
---|
227 | ! & debut, & |
---|
228 | ! & tsurf_new, alb_new, z0_new, pctsrf_new) |
---|
229 | ! endif |
---|
230 | ! |
---|
231 | call calcul_fluxs( knon, dtime, & |
---|
232 | & tsurf, p1lay, cal, beta, coef1lay, ps, & |
---|
233 | & radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, & |
---|
234 | & petAcoef, peqAcoef, petBcoef, peqBcoef, & |
---|
235 | & tsurf_new, fluxlat, fluxsens, dflux_s, dflux_l) |
---|
236 | ! |
---|
237 | else if (nisurf == is_sic) then |
---|
238 | |
---|
239 | if (check) write(*,*)'sea ice, nisurf = ',nisurf |
---|
240 | |
---|
241 | ! |
---|
242 | ! Surface "glace de mer" appel a l'interface avec l'ocean |
---|
243 | ! |
---|
244 | ! call interfoce(nisurf, ocean) |
---|
245 | ! |
---|
246 | call calcul_fluxs( knon, dtime, & |
---|
247 | & tsurf, p1lay, cal, beta, coef1lay, ps, & |
---|
248 | & radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, & |
---|
249 | & petAcoef, peqAcoef, petBcoef, peqBcoef, & |
---|
250 | & tsurf_new, fluxlat, fluxsens, dflux_s, dflux_l) |
---|
251 | |
---|
252 | else if (nisurf == is_lic) then |
---|
253 | |
---|
254 | if (check) write(*,*)'glacier, nisurf = ',nisurf |
---|
255 | |
---|
256 | ! |
---|
257 | ! Surface "glacier continentaux" appel a l'interface avec le sol |
---|
258 | ! |
---|
259 | ! call interfsol(nisurf) |
---|
260 | call calcul_fluxs( knon, dtime, & |
---|
261 | & tsurf, p1lay, cal, beta, coef1lay, ps, & |
---|
262 | & radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, & |
---|
263 | & petAcoef, peqAcoef, petBcoef, peqBcoef, & |
---|
264 | & tsurf_new, fluxlat, fluxsens, dflux_s, dflux_l) |
---|
265 | |
---|
266 | else |
---|
267 | write(*,*)'Index surface = ',nisurf |
---|
268 | abort_message = 'Index surface non valable' |
---|
269 | call abort_gcm(modname,abort_message,1) |
---|
270 | endif |
---|
271 | |
---|
272 | END SUBROUTINE interfsurf_hq |
---|
273 | |
---|
274 | ! |
---|
275 | !######################################################################### |
---|
276 | ! |
---|
277 | SUBROUTINE interfsurf_vent(nisurf, knon & |
---|
278 | & ) |
---|
279 | ! |
---|
280 | ! Cette routine sert d'aiguillage entre l'atmosphere et la surface en general |
---|
281 | ! (sols continentaux, oceans, glaces) pour les tensions de vents. |
---|
282 | ! En pratique l'interface se fait entre la couche limite du modele |
---|
283 | ! atmospherique (clmain.F) et les routines de surface (sechiba, oasis, ...) |
---|
284 | ! |
---|
285 | ! |
---|
286 | ! L.Fairhead 02/2000 |
---|
287 | ! |
---|
288 | ! input: |
---|
289 | ! nisurf index de la surface a traiter (1 = sol continental) |
---|
290 | ! knon nombre de points de la surface a traiter |
---|
291 | |
---|
292 | ! Parametres d'entree |
---|
293 | integer, intent(IN) :: nisurf |
---|
294 | integer, intent(IN) :: knon |
---|
295 | |
---|
296 | |
---|
297 | return |
---|
298 | END SUBROUTINE interfsurf_vent |
---|
299 | ! |
---|
300 | !######################################################################### |
---|
301 | ! |
---|
302 | SUBROUTINE interfsol(itime, klon, dtime, nisurf, knon, & |
---|
303 | & knindex, rlon, rlat, & |
---|
304 | & debut, lafin, ok_veget, & |
---|
305 | & zlev, zlflu, u1_lay, v1_lay, temp_air, spechum, hum_air, ccanopy, & |
---|
306 | & tq_cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, & |
---|
307 | & precip_rain, precip_snow, lwdown, swnet, swdown, & |
---|
308 | & tsurf, p1lay, cal, beta, coef1lay, ps, radsol, dif_grnd, & |
---|
309 | & evap, fluxsens, fluxlat, & |
---|
310 | & tsol_rad, tsurf_new, alb_new, emis_new, z0_new, dflux_l, dflux_s) |
---|
311 | |
---|
312 | ! Cette routine sert d'interface entre le modele atmospherique et le |
---|
313 | ! modele de sol continental. Appel a sechiba |
---|
314 | ! |
---|
315 | ! L. Fairhead 02/2000 |
---|
316 | ! |
---|
317 | ! input: |
---|
318 | ! itime numero du pas de temps |
---|
319 | ! klon nombre total de points de grille |
---|
320 | ! dtime pas de temps de la physique (en s) |
---|
321 | ! nisurf index de la surface a traiter (1 = sol continental) |
---|
322 | ! knon nombre de points de la surface a traiter |
---|
323 | ! knindex index des points de la surface a traiter |
---|
324 | ! rlon longitudes de la grille entiere |
---|
325 | ! rlat latitudes de la grille entiere |
---|
326 | ! debut logical: 1er appel a la physique (lire les restart) |
---|
327 | ! lafin logical: dernier appel a la physique (ecrire les restart) |
---|
328 | ! ok_veget logical: appel ou non au schema de surface continental |
---|
329 | ! (si false calcul simplifie des fluxs sur les continents) |
---|
330 | ! zlev hauteur de la premiere couche |
---|
331 | ! zlflu |
---|
332 | ! u1_lay vitesse u 1ere couche |
---|
333 | ! v1_lay vitesse v 1ere couche |
---|
334 | ! temp_air temperature de l'air 1ere couche |
---|
335 | ! spechum humidite specifique 1ere couche |
---|
336 | ! hum_air humidite de l'air |
---|
337 | ! ccanopy concentration CO2 canopee |
---|
338 | ! tq_cdrag cdrag |
---|
339 | ! petAcoef coeff. A de la resolution de la CL pour t |
---|
340 | ! peqAcoef coeff. A de la resolution de la CL pour q |
---|
341 | ! petBcoef coeff. B de la resolution de la CL pour t |
---|
342 | ! peqBcoef coeff. B de la resolution de la CL pour q |
---|
343 | ! precip_rain precipitation liquide |
---|
344 | ! precip_snow precipitation solide |
---|
345 | ! lwdown flux IR entrant a la surface |
---|
346 | ! swnet flux solaire net |
---|
347 | ! swdown flux solaire entrant a la surface |
---|
348 | ! tsurf temperature de surface |
---|
349 | ! p1lay pression 1er niveau (milieu de couche) |
---|
350 | ! cal capacite calorifique du sol |
---|
351 | ! beta evap reelle |
---|
352 | ! coef1lay coefficient d'echange |
---|
353 | ! ps pression au sol |
---|
354 | ! radsol rayonnement net aus sol (LW + SW) |
---|
355 | ! dif_grnd coeff. diffusion vers le sol profond |
---|
356 | ! |
---|
357 | ! |
---|
358 | ! input/output |
---|
359 | ! run_off ruissellement total |
---|
360 | ! |
---|
361 | ! output: |
---|
362 | ! evap evaporation totale |
---|
363 | ! fluxsens flux de chaleur sensible |
---|
364 | ! fluxlat flux de chaleur latente |
---|
365 | ! tsol_rad |
---|
366 | ! tsurf_new temperature au sol |
---|
367 | ! alb_new albedo |
---|
368 | ! emis_new emissivite |
---|
369 | ! z0_new surface roughness |
---|
370 | |
---|
371 | ! Parametres d'entree |
---|
372 | integer, intent(IN) :: itime |
---|
373 | integer, intent(IN) :: klon |
---|
374 | real, intent(IN) :: dtime |
---|
375 | integer, intent(IN) :: nisurf |
---|
376 | integer, intent(IN) :: knon |
---|
377 | integer, dimension(knon), intent(IN) :: knindex |
---|
378 | logical, intent(IN) :: debut, lafin, ok_veget |
---|
379 | real, dimension(klon), intent(IN) :: rlon, rlat |
---|
380 | real, dimension(knon), intent(IN) :: zlev, zlflu |
---|
381 | real, dimension(knon), intent(IN) :: u1_lay, v1_lay |
---|
382 | real, dimension(knon), intent(IN) :: temp_air, spechum |
---|
383 | real, dimension(knon), intent(IN) :: hum_air, ccanopy |
---|
384 | real, dimension(knon), intent(IN) :: tq_cdrag, petAcoef, peqAcoef |
---|
385 | real, dimension(knon), intent(IN) :: petBcoef, peqBcoef |
---|
386 | real, dimension(knon), intent(IN) :: precip_rain, precip_snow |
---|
387 | real, dimension(knon), intent(IN) :: lwdown, swnet, swdown, ps |
---|
388 | real, dimension(knon), intent(IN) :: tsurf, p1lay, cal, beta, coef1lay |
---|
389 | real, dimension(knon), intent(IN) :: radsol, dif_grnd |
---|
390 | ! Parametres de sortie |
---|
391 | real, dimension(knon), intent(OUT):: evap, fluxsens, fluxlat |
---|
392 | real, dimension(knon), intent(OUT):: tsol_rad, tsurf_new, alb_new |
---|
393 | real, dimension(knon), intent(OUT):: emis_new, z0_new |
---|
394 | real, dimension(knon), intent(OUT):: dflux_s, dflux_l |
---|
395 | |
---|
396 | ! Local |
---|
397 | ! |
---|
398 | integer :: ii |
---|
399 | integer :: error |
---|
400 | character (len = 20) :: modname = 'interfsol' |
---|
401 | character (len = 80) :: abort_message |
---|
402 | logical :: check = .true. |
---|
403 | ! type de couplage dans sechiba |
---|
404 | ! character (len=10) :: coupling = 'implicit' |
---|
405 | ! drapeaux controlant les appels dans SECHIBA |
---|
406 | ! type(control_type), save :: control_in |
---|
407 | ! coordonnees geographiques |
---|
408 | real, allocatable, dimension(:,:), save :: lalo |
---|
409 | ! pts voisins |
---|
410 | integer,allocatable, dimension(:,:), save :: neighbours |
---|
411 | ! resolution de la grille |
---|
412 | real, allocatable, dimension (:,:), save :: resolution |
---|
413 | ! Identifieurs des fichiers restart et histoire |
---|
414 | integer, save :: rest_id, hist_id |
---|
415 | integer, save :: rest_id_stom, hist_id_stom |
---|
416 | |
---|
417 | if (check) write(*,*)'Entree ', modname |
---|
418 | if (check) write(*,*)'ok_veget = ',ok_veget |
---|
419 | |
---|
420 | ! initialisation |
---|
421 | if (.not. ok_veget) then |
---|
422 | call calcul_fluxs( knon, dtime, & |
---|
423 | & tsurf, p1lay, cal, beta, coef1lay, ps, & |
---|
424 | & radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, & |
---|
425 | & petAcoef, peqAcoef, petBcoef, peqBcoef, & |
---|
426 | & tsurf_new, fluxlat, fluxsens, dflux_s, dflux_l) |
---|
427 | else |
---|
428 | ! if (debut) then |
---|
429 | ! ! |
---|
430 | ! ! Configuration de parametres specifiques a la SSL |
---|
431 | ! ! |
---|
432 | ! call intsurf_config(control_in) |
---|
433 | ! ! |
---|
434 | ! ! Allouer et initialiser le tableau de coordonnees du sol |
---|
435 | ! ! |
---|
436 | ! if (( .not. allocated(lalo))) then |
---|
437 | ! allocate(lalo(knon,2), stat = error) |
---|
438 | ! if (error /= 0) then |
---|
439 | ! abort_message='Pb allocation lalo' |
---|
440 | ! call abort_gcm(modname,abort_message,1) |
---|
441 | ! endif |
---|
442 | ! endif |
---|
443 | ! do ii = 1, knon |
---|
444 | ! lalo(ii,1) = rlat(knindex(ii)) |
---|
445 | ! lalo(ii,2) = rlon(knindex(ii)) |
---|
446 | ! enddo |
---|
447 | !- |
---|
448 | !- Compute variable to help describe the grid |
---|
449 | !- once the points are gathered. |
---|
450 | !- |
---|
451 | ! IF ( (.NOT.ALLOCATED(neighbours))) THEN |
---|
452 | ! ALLOCATE(neighbours(knon,4), stat = error) |
---|
453 | ! if (error /= 0) then |
---|
454 | ! abort_message='Pb allocation neighbours' |
---|
455 | ! call abort_gcm(modname,abort_message,1) |
---|
456 | ! endif |
---|
457 | ! ENDIF |
---|
458 | ! IF ( (.NOT.ALLOCATED(resolution))) THEN |
---|
459 | ! ALLOCATE(resolution(knon,2), stat = error) |
---|
460 | ! if (error /= 0) then |
---|
461 | ! abort_message='Pb allocation resolution' |
---|
462 | ! call abort_gcm(modname,abort_message,1) |
---|
463 | ! endif |
---|
464 | ! ENDIF |
---|
465 | |
---|
466 | ! call grid_stuff |
---|
467 | ! call sechiba_restart_init |
---|
468 | ! call sechiba_history_init |
---|
469 | |
---|
470 | ! endif ! (fin debut) |
---|
471 | |
---|
472 | ! |
---|
473 | ! Appel a la routine sols continentaux |
---|
474 | ! |
---|
475 | |
---|
476 | ! call sechiba_main(itime, klon, knon, knindex, dtime, & |
---|
477 | ! & debut, lafin, coupling, control_in, & |
---|
478 | ! & lalo, neighbours, resolution,& |
---|
479 | ! & zlev, zlflu, u1_lay, v1_lay, spechum, temp_air,hum_air , ccanopy, & |
---|
480 | ! & tq_cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, & |
---|
481 | ! & precip_rain, precip_snow, lwdown, swnet, swdown, ps, & |
---|
482 | ! & evap, fluxsens, fluxlat, & |
---|
483 | ! & tsol_rad, tsurf_new, alb_new, emis_new, z0_new, & |
---|
484 | ! & rest_id, hist_id, rest_id_stom, hist_id_stom) |
---|
485 | |
---|
486 | ! |
---|
487 | ! Sauvegarde dans fichiers histoire |
---|
488 | ! |
---|
489 | endif ! fin ok_veget |
---|
490 | |
---|
491 | END SUBROUTINE interfsol |
---|
492 | ! |
---|
493 | !######################################################################### |
---|
494 | ! |
---|
495 | SUBROUTINE interfoce_cpl(nisurf, ocean) |
---|
496 | |
---|
497 | ! Cette routine sert d'interface entre le modele atmospherique et un |
---|
498 | ! coupleur avec un modele d'ocean 'complet' |
---|
499 | ! |
---|
500 | ! L. Fairhead 02/2000 |
---|
501 | ! |
---|
502 | ! input: |
---|
503 | ! nisurf index de la surface a traiter (1 = sol continental) |
---|
504 | ! ocean type d'ocean |
---|
505 | ! |
---|
506 | ! output: |
---|
507 | ! |
---|
508 | |
---|
509 | ! Parametres d'entree |
---|
510 | integer, intent(IN) :: nisurf |
---|
511 | character (len = 6) :: ocean |
---|
512 | |
---|
513 | ! Parametres de sortie |
---|
514 | |
---|
515 | ! Variables locales |
---|
516 | |
---|
517 | |
---|
518 | ! Initialisation |
---|
519 | ! fichier restart et fichiers histoires |
---|
520 | |
---|
521 | ! calcul des fluxs a passer |
---|
522 | |
---|
523 | END SUBROUTINE interfoce_cpl |
---|
524 | ! |
---|
525 | !######################################################################### |
---|
526 | ! |
---|
527 | SUBROUTINE interfoce_slab(nisurf) |
---|
528 | |
---|
529 | ! Cette routine sert d'interface entre le modele atmospherique et un |
---|
530 | ! modele de 'slab' ocean |
---|
531 | ! |
---|
532 | ! L. Fairhead 02/2000 |
---|
533 | ! |
---|
534 | ! input: |
---|
535 | ! nisurf index de la surface a traiter (1 = sol continental) |
---|
536 | ! |
---|
537 | ! output: |
---|
538 | ! |
---|
539 | |
---|
540 | ! Parametres d'entree |
---|
541 | integer, intent(IN) :: nisurf |
---|
542 | |
---|
543 | END SUBROUTINE interfoce_slab |
---|
544 | ! |
---|
545 | !######################################################################### |
---|
546 | ! |
---|
547 | SUBROUTINE interfoce_lim(itime, dtime, jour, & |
---|
548 | & klon, nisurf, knon, knindex, & |
---|
549 | & debut, & |
---|
550 | & lmt_sst, lmt_alb, lmt_rug, pctsrf_new) |
---|
551 | |
---|
552 | ! Cette routine sert d'interface entre le modele atmospherique et un fichier |
---|
553 | ! de conditions aux limites |
---|
554 | ! |
---|
555 | ! L. Fairhead 02/2000 |
---|
556 | ! |
---|
557 | ! input: |
---|
558 | ! itime numero du pas de temps courant |
---|
559 | ! dtime pas de temps de la physique (en s) |
---|
560 | ! jour jour a lire dans l'annee |
---|
561 | ! nisurf index de la surface a traiter (1 = sol continental) |
---|
562 | ! knon nombre de points dans le domaine a traiter |
---|
563 | ! knindex index des points de la surface a traiter |
---|
564 | ! klon taille de la grille |
---|
565 | ! debut logical: 1er appel a la physique (initialisation) |
---|
566 | ! |
---|
567 | ! output: |
---|
568 | ! lmt_sst SST lues dans le fichier de CL |
---|
569 | ! lmt_alb Albedo lu |
---|
570 | ! lmt_rug longueur de rugosité lue |
---|
571 | ! pctsrf_new sous-maille fractionnelle |
---|
572 | ! |
---|
573 | |
---|
574 | |
---|
575 | ! Parametres d'entree |
---|
576 | integer, intent(IN) :: itime |
---|
577 | real , intent(IN) :: dtime |
---|
578 | integer, intent(IN) :: jour |
---|
579 | integer, intent(IN) :: nisurf |
---|
580 | integer, intent(IN) :: knon |
---|
581 | integer, intent(IN) :: klon |
---|
582 | integer, dimension(knon), intent(in) :: knindex |
---|
583 | logical, intent(IN) :: debut |
---|
584 | |
---|
585 | ! Parametres de sortie |
---|
586 | real, intent(out), dimension(knon) :: lmt_sst |
---|
587 | real, intent(out), dimension(knon) :: lmt_alb |
---|
588 | real, intent(out), dimension(knon) :: lmt_rug |
---|
589 | real, intent(out), dimension(klon,nbsrf) :: pctsrf_new |
---|
590 | |
---|
591 | ! Variables locales |
---|
592 | integer :: ii |
---|
593 | integer :: lmt_pas ! frequence de lecture des conditions limites |
---|
594 | ! (en pas de physique) |
---|
595 | logical,save :: deja_lu ! pour indiquer que le jour a lire a deja |
---|
596 | ! lu pour une surface precedente |
---|
597 | integer,save :: jour_lu |
---|
598 | integer :: ierr |
---|
599 | character (len = 20) :: modname = 'interfoce_lim' |
---|
600 | character (len = 80) :: abort_message |
---|
601 | character (len = 20) :: fich ='limit' |
---|
602 | logical :: newlmt = .false. |
---|
603 | logical :: check = .true. |
---|
604 | ! Champs lus dans le fichier de CL |
---|
605 | real, allocatable , save, dimension(:) :: sst_lu, alb_lu, rug_lu, nat_lu |
---|
606 | real, allocatable , save, dimension(:,:) :: pct_tmp |
---|
607 | ! |
---|
608 | ! quelques variables pour netcdf |
---|
609 | ! |
---|
610 | #include "netcdf.inc" |
---|
611 | integer :: nid, nvarid |
---|
612 | integer, dimension(2) :: start, epais |
---|
613 | ! |
---|
614 | ! Fin déclaration |
---|
615 | ! |
---|
616 | |
---|
617 | if (debut) then |
---|
618 | lmt_pas = nint(86400./dtime * 1.0) ! pour une lecture une fois par jour |
---|
619 | jour_lu = jour - 1 |
---|
620 | allocate(sst_lu(klon)) |
---|
621 | allocate(alb_lu(klon)) |
---|
622 | allocate(rug_lu(klon)) |
---|
623 | allocate(nat_lu(klon)) |
---|
624 | allocate(pct_tmp(klon,nbsrf)) |
---|
625 | endif |
---|
626 | |
---|
627 | if ((jour - jour_lu) /= 0) deja_lu = .false. |
---|
628 | |
---|
629 | if (check) write(*,*)modname,' :: jour_lu, deja_lu', jour_lu, deja_lu |
---|
630 | |
---|
631 | ! Tester d'abord si c'est le moment de lire le fichier |
---|
632 | if (mod(itime-1, lmt_pas) == 0 .and. .not. deja_lu) then |
---|
633 | ! |
---|
634 | ! Ouverture du fichier |
---|
635 | ! |
---|
636 | ierr = NF_OPEN (fich, NF_NOWRITE,nid) |
---|
637 | if (ierr.NE.NF_NOERR) then |
---|
638 | abort_message = 'Pb d''ouverture du fichier de conditions aux limites' |
---|
639 | call abort_gcm(modname,abort_message,1) |
---|
640 | endif |
---|
641 | ! |
---|
642 | ! La tranche de donnees a lire: |
---|
643 | ! |
---|
644 | start(1) = 1 |
---|
645 | start(2) = jour + 1 |
---|
646 | epais(1) = klon |
---|
647 | epais(2) = 1 |
---|
648 | ! |
---|
649 | if (newlmt) then |
---|
650 | ! |
---|
651 | ! Fraction "ocean" |
---|
652 | ! |
---|
653 | ierr = NF_INQ_VARID(nid, 'FOCE', nvarid) |
---|
654 | if (ierr /= NF_NOERR) then |
---|
655 | abort_message = 'Le champ <FOCE> est absent' |
---|
656 | call abort_gcm(modname,abort_message,1) |
---|
657 | endif |
---|
658 | #ifdef NC_DOUBLE |
---|
659 | ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais,pctsrf_new(1,is_oce)) |
---|
660 | #else |
---|
661 | ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais,pctsrf_new(1,is_oce)) |
---|
662 | #endif |
---|
663 | if (ierr /= NF_NOERR) then |
---|
664 | abort_message = 'Lecture echouee pour <FOCE>' |
---|
665 | call abort_gcm(modname,abort_message,1) |
---|
666 | endif |
---|
667 | ! |
---|
668 | ! Fraction "glace de mer" |
---|
669 | ! |
---|
670 | ierr = NF_INQ_VARID(nid, 'FSIC', nvarid) |
---|
671 | if (ierr /= NF_NOERR) then |
---|
672 | abort_message = 'Le champ <FSIC> est absent' |
---|
673 | call abort_gcm(modname,abort_message,1) |
---|
674 | endif |
---|
675 | #ifdef NC_DOUBLE |
---|
676 | ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais,pctsrf_new(1,is_sic)) |
---|
677 | #else |
---|
678 | ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais,pctsrf_new(1,is_sic)) |
---|
679 | #endif |
---|
680 | if (ierr /= NF_NOERR) then |
---|
681 | abort_message = 'Lecture echouee pour <FSIC>' |
---|
682 | call abort_gcm(modname,abort_message,1) |
---|
683 | endif |
---|
684 | ! |
---|
685 | ! Fraction "terre" |
---|
686 | ! |
---|
687 | ierr = NF_INQ_VARID(nid, 'FTER', nvarid) |
---|
688 | if (ierr /= NF_NOERR) then |
---|
689 | abort_message = 'Le champ <FTER> est absent' |
---|
690 | call abort_gcm(modname,abort_message,1) |
---|
691 | endif |
---|
692 | #ifdef NC_DOUBLE |
---|
693 | ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais,pctsrf_new(1,is_ter)) |
---|
694 | #else |
---|
695 | ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais,pctsrf_new(1,is_ter)) |
---|
696 | #endif |
---|
697 | if (ierr /= NF_NOERR) then |
---|
698 | abort_message = 'Lecture echouee pour <FTER>' |
---|
699 | call abort_gcm(modname,abort_message,1) |
---|
700 | endif |
---|
701 | ! |
---|
702 | ! Fraction "glacier terre" |
---|
703 | ! |
---|
704 | ierr = NF_INQ_VARID(nid, 'FLIC', nvarid) |
---|
705 | if (ierr /= NF_NOERR) then |
---|
706 | abort_message = 'Le champ <FLIC> est absent' |
---|
707 | call abort_gcm(modname,abort_message,1) |
---|
708 | endif |
---|
709 | #ifdef NC_DOUBLE |
---|
710 | ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais,pctsrf_new(1,is_lic)) |
---|
711 | #else |
---|
712 | ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais,pctsrf_new(1,is_lic)) |
---|
713 | #endif |
---|
714 | if (ierr /= NF_NOERR) then |
---|
715 | abort_message = 'Lecture echouee pour <FLIC>' |
---|
716 | call abort_gcm(modname,abort_message,1) |
---|
717 | endif |
---|
718 | ! |
---|
719 | else ! on en est toujours a rnatur |
---|
720 | ! |
---|
721 | ierr = NF_INQ_VARID(nid, 'NAT', nvarid) |
---|
722 | if (ierr /= NF_NOERR) then |
---|
723 | abort_message = 'Le champ <NAT> est absent' |
---|
724 | call abort_gcm(modname,abort_message,1) |
---|
725 | endif |
---|
726 | #ifdef NC_DOUBLE |
---|
727 | ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais, nat_lu) |
---|
728 | #else |
---|
729 | ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais, nat_lu) |
---|
730 | #endif |
---|
731 | if (ierr /= NF_NOERR) then |
---|
732 | abort_message = 'Lecture echouee pour <NAT>' |
---|
733 | call abort_gcm(modname,abort_message,1) |
---|
734 | endif |
---|
735 | ! |
---|
736 | ! Remplissage des fractions de surface |
---|
737 | ! nat = 0, 1, 2, 3 pour ocean, terre, glacier, seaice |
---|
738 | ! |
---|
739 | pct_tmp = 0.0 |
---|
740 | do ii = 1, klon |
---|
741 | pct_tmp(ii,nint(nat_lu(ii)) + 1) = 1. |
---|
742 | enddo |
---|
743 | |
---|
744 | ! |
---|
745 | ! On se retrouve avec ocean en 1 et terre en 2 alors qu'on veut le contraire |
---|
746 | ! |
---|
747 | pctsrf_new = pct_tmp |
---|
748 | pctsrf_new (:,2)= pct_tmp (:,1) |
---|
749 | pctsrf_new (:,1)= pct_tmp (:,2) |
---|
750 | pct_tmp = pctsrf_new |
---|
751 | endif ! fin test sur newlmt |
---|
752 | ! |
---|
753 | ! Lecture SST |
---|
754 | ! |
---|
755 | ierr = NF_INQ_VARID(nid, 'SST', nvarid) |
---|
756 | if (ierr /= NF_NOERR) then |
---|
757 | abort_message = 'Le champ <SST> est absent' |
---|
758 | call abort_gcm(modname,abort_message,1) |
---|
759 | endif |
---|
760 | #ifdef NC_DOUBLE |
---|
761 | ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais, sst_lu) |
---|
762 | #else |
---|
763 | ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais, sst_lu) |
---|
764 | #endif |
---|
765 | if (ierr /= NF_NOERR) then |
---|
766 | abort_message = 'Lecture echouee pour <SST>' |
---|
767 | call abort_gcm(modname,abort_message,1) |
---|
768 | endif |
---|
769 | ! |
---|
770 | ! Lecture Albedo |
---|
771 | ! |
---|
772 | ierr = NF_INQ_VARID(nid, 'ALB', nvarid) |
---|
773 | if (ierr /= NF_NOERR) then |
---|
774 | abort_message = 'Le champ <ALB> est absent' |
---|
775 | call abort_gcm(modname,abort_message,1) |
---|
776 | endif |
---|
777 | #ifdef NC_DOUBLE |
---|
778 | ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais, alb_lu) |
---|
779 | #else |
---|
780 | ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais, alb_lu) |
---|
781 | #endif |
---|
782 | if (ierr /= NF_NOERR) then |
---|
783 | abort_message = 'Lecture echouee pour <ALB>' |
---|
784 | call abort_gcm(modname,abort_message,1) |
---|
785 | endif |
---|
786 | ! |
---|
787 | ! Lecture rugosité |
---|
788 | ! |
---|
789 | ierr = NF_INQ_VARID(nid, 'RUG', nvarid) |
---|
790 | if (ierr /= NF_NOERR) then |
---|
791 | abort_message = 'Le champ <RUG> est absent' |
---|
792 | call abort_gcm(modname,abort_message,1) |
---|
793 | endif |
---|
794 | #ifdef NC_DOUBLE |
---|
795 | ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais, rug_lu) |
---|
796 | #else |
---|
797 | ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais, rug_lu) |
---|
798 | #endif |
---|
799 | if (ierr /= NF_NOERR) then |
---|
800 | abort_message = 'Lecture echouee pour <RUG>' |
---|
801 | call abort_gcm(modname,abort_message,1) |
---|
802 | endif |
---|
803 | |
---|
804 | ! |
---|
805 | ! Fin de lecture |
---|
806 | ! |
---|
807 | ierr = NF_CLOSE(nid) |
---|
808 | deja_lu = .true. |
---|
809 | jour_lu = jour |
---|
810 | endif |
---|
811 | ! |
---|
812 | ! Recopie des variables dans les champs de sortie |
---|
813 | ! |
---|
814 | do ii = 1, knon |
---|
815 | lmt_sst(ii) = sst_lu(knindex(ii)) |
---|
816 | lmt_alb(ii) = alb_lu(knindex(ii)) |
---|
817 | lmt_rug(ii) = rug_lu(knindex(ii)) |
---|
818 | enddo |
---|
819 | pctsrf_new = pct_tmp |
---|
820 | |
---|
821 | END SUBROUTINE interfoce_lim |
---|
822 | |
---|
823 | ! |
---|
824 | !######################################################################### |
---|
825 | ! |
---|
826 | |
---|
827 | SUBROUTINE calcul_fluxs( knon, dtime, & |
---|
828 | & tsurf, p1lay, cal, beta, coef1lay, ps, & |
---|
829 | & radsol, dif_grnd, t1lay, q1lay, u1lay, v1lay, & |
---|
830 | & petAcoef, peqAcoef, petBcoef, peqBcoef, & |
---|
831 | & tsurf_new, fluxlat, fluxsens, dflux_s, dflux_l) |
---|
832 | |
---|
833 | ! Cette routine calcule les fluxs en h et q a l'interface et eventuellement |
---|
834 | ! une temperature de surface (au cas ou ok_veget = false) |
---|
835 | ! |
---|
836 | ! L. Fairhead 4/2000 |
---|
837 | ! |
---|
838 | ! input: |
---|
839 | ! knon nombre de points a traiter |
---|
840 | ! tsurf temperature de surface |
---|
841 | ! p1lay pression 1er niveau (milieu de couche) |
---|
842 | ! cal capacite calorifique du sol |
---|
843 | ! beta evap reelle |
---|
844 | ! coef1lay coefficient d'echange |
---|
845 | ! ps pression au sol |
---|
846 | ! petAcoef coeff. A de la resolution de la CL pour t |
---|
847 | ! peqAcoef coeff. A de la resolution de la CL pour q |
---|
848 | ! petBcoef coeff. B de la resolution de la CL pour t |
---|
849 | ! peqBcoef coeff. B de la resolution de la CL pour q |
---|
850 | ! radsol rayonnement net aus sol (LW + SW) |
---|
851 | ! dif_grnd coeff. diffusion vers le sol profond |
---|
852 | ! |
---|
853 | ! output: |
---|
854 | ! tsurf_new temperature au sol |
---|
855 | ! fluxsens flux de chaleur sensible |
---|
856 | ! fluxlat flux de chaleur latente |
---|
857 | ! dflux_s derivee du flux de chaleur sensible / Ts |
---|
858 | ! dflux_l derivee du flux de chaleur latente / Ts |
---|
859 | ! |
---|
860 | |
---|
861 | #include "YOMCST.inc" |
---|
862 | #include "YOETHF.inc" |
---|
863 | #include "FCTTRE.inc" |
---|
864 | |
---|
865 | ! Parametres d'entree |
---|
866 | integer, intent(IN) :: knon |
---|
867 | real , intent(IN) :: dtime |
---|
868 | real, dimension(knon), intent(IN) :: petAcoef, peqAcoef |
---|
869 | real, dimension(knon), intent(IN) :: petBcoef, peqBcoef |
---|
870 | real, dimension(knon), intent(IN) :: ps, q1lay |
---|
871 | real, dimension(knon), intent(IN) :: tsurf, p1lay, cal, beta, coef1lay |
---|
872 | real, dimension(knon), intent(IN) :: radsol, dif_grnd |
---|
873 | real, dimension(knon), intent(IN) :: t1lay, u1lay, v1lay |
---|
874 | |
---|
875 | ! Parametres sorties |
---|
876 | real, dimension(knon), intent(OUT):: tsurf_new, fluxlat, fluxsens |
---|
877 | real, dimension(knon), intent(OUT):: dflux_s, dflux_l |
---|
878 | |
---|
879 | ! Variables locales |
---|
880 | integer :: i |
---|
881 | real, dimension(knon) :: zx_mh, zx_nh, zx_oh |
---|
882 | real, dimension(knon) :: zx_mq, zx_nq, zx_oq |
---|
883 | real, dimension(knon) :: zx_pkh, zx_dq_s_dt, zx_qsat, zx_coef |
---|
884 | real, dimension(knon) :: zx_sl, zx_k1, zx_dq, zx_cq, zx_dh, zx_ch |
---|
885 | real, dimension(knon) :: zx_h_ts, zx_q_0 , d_ts |
---|
886 | real :: zdelta, zcvm5, zx_qs, zcor, zx_dq_s_dh |
---|
887 | real, parameter :: t_grnd = 271.35, t_coup = 273.15 |
---|
888 | logical :: check = .true. |
---|
889 | character (len = 20) :: modname = 'calcul_fluxs' |
---|
890 | |
---|
891 | if (check) write(*,*)'Entree ', modname |
---|
892 | ! |
---|
893 | ! Initialisation |
---|
894 | ! |
---|
895 | ! |
---|
896 | ! zx_qs = qsat en kg/kg |
---|
897 | ! |
---|
898 | DO i = 1, knon |
---|
899 | zx_pkh(i) = (ps(i)/ps(i))**RKAPPA |
---|
900 | IF (thermcep) THEN |
---|
901 | zdelta=MAX(0.,SIGN(1.,rtt-tsurf(i))) |
---|
902 | zcvm5 = R5LES*RLVTT*(1.-zdelta) + R5IES*RLSTT*zdelta |
---|
903 | zcvm5 = zcvm5 / RCPD / (1.0+RVTMP2*q1lay(i)) |
---|
904 | zx_qs= r2es * FOEEW(tsurf(i),zdelta)/ps(i) |
---|
905 | zx_qs=MIN(0.5,zx_qs) |
---|
906 | zcor=1./(1.-retv*zx_qs) |
---|
907 | zx_qs=zx_qs*zcor |
---|
908 | zx_dq_s_dh = FOEDE(tsurf(i),zdelta,zcvm5,zx_qs,zcor) & |
---|
909 | & /RLVTT / zx_pkh(i) |
---|
910 | ELSE |
---|
911 | IF (tsurf(i).LT.t_coup) THEN |
---|
912 | zx_qs = qsats(tsurf(i)) / ps(i) |
---|
913 | zx_dq_s_dh = dqsats(tsurf(i),zx_qs)/RLVTT & |
---|
914 | & / zx_pkh(i) |
---|
915 | ELSE |
---|
916 | zx_qs = qsatl(tsurf(i)) / ps(i) |
---|
917 | zx_dq_s_dh = dqsatl(tsurf(i),zx_qs)/RLVTT & |
---|
918 | & / zx_pkh(i) |
---|
919 | ENDIF |
---|
920 | ENDIF |
---|
921 | zx_dq_s_dt(i) = RCPD * zx_pkh(i) * zx_dq_s_dh |
---|
922 | zx_qsat(i) = zx_qs |
---|
923 | zx_coef(i) = coef1lay(i) & |
---|
924 | & * (1.0+SQRT(u1lay(i)**2+v1lay(i)**2)) & |
---|
925 | & * p1lay(i)/(RD*t1lay(i)) |
---|
926 | |
---|
927 | ENDDO |
---|
928 | |
---|
929 | |
---|
930 | ! === Calcul de la temperature de surface === |
---|
931 | ! |
---|
932 | ! zx_sl = chaleur latente d'evaporation ou de sublimation |
---|
933 | ! |
---|
934 | do i = 1, knon |
---|
935 | zx_sl(i) = RLVTT |
---|
936 | if (tsurf(i) .LT. RTT) zx_sl(i) = RLSTT |
---|
937 | zx_k1(i) = zx_coef(i) |
---|
938 | enddo |
---|
939 | |
---|
940 | |
---|
941 | do i = 1, knon |
---|
942 | ! Q |
---|
943 | zx_oq(i) = 1. - (beta(i) * zx_k1(i) * peqBcoef(i) * dtime) |
---|
944 | zx_mq(i) = beta(i) * zx_k1(i) * & |
---|
945 | & (peqAcoef(i) - zx_qsat(i) & |
---|
946 | & + zx_dq_s_dt(i) * tsurf(i)) & |
---|
947 | & / zx_oq(i) |
---|
948 | zx_nq(i) = beta(i) * zx_k1(i) * (-1. * zx_dq_s_dt(i)) & |
---|
949 | & / zx_oq(i) |
---|
950 | |
---|
951 | ! H |
---|
952 | zx_oh(i) = 1. - (zx_k1(i) * petBcoef(i) * dtime) |
---|
953 | zx_mh(i) = zx_k1(i) * petAcoef(i) / zx_oh(i) |
---|
954 | zx_nh(i) = - (zx_k1(i) * RCPD * zx_pkh(i))/ zx_oh(i) |
---|
955 | |
---|
956 | ! Tsurface |
---|
957 | tsurf_new(i) = (tsurf(i) + cal(i)/(RCPD * zx_pkh(i)) * dtime * & |
---|
958 | & (radsol(i) + zx_mh(i) + zx_sl(i) * zx_mq(i)) & |
---|
959 | & + dif_grnd(i) * t_grnd * dtime)/ & |
---|
960 | & ( 1. - dtime * cal(i)/(RCPD * zx_pkh(i)) * ( & |
---|
961 | & zx_nh(i) + zx_sl(i) * zx_nq(i)) & |
---|
962 | & + dtime * dif_grnd(i)) |
---|
963 | zx_h_ts(i) = tsurf_new(i) * RCPD * zx_pkh(i) |
---|
964 | d_ts(i) = tsurf_new(i) - tsurf(i) |
---|
965 | zx_q_0(i) = zx_qsat(i) + zx_dq_s_dt(i) * d_ts(i) |
---|
966 | !== flux_q est le flux de vapeur d'eau: kg/(m**2 s) positive vers bas |
---|
967 | !== flux_t est le flux de cpt (energie sensible): j/(m**2 s) |
---|
968 | fluxlat(i) = zx_mq(i) + zx_nq(i) * tsurf_new(i) |
---|
969 | fluxsens(i) = zx_mh(i) + zx_nh(i) * tsurf_new(i) |
---|
970 | ! Derives des flux dF/dTs (W m-2 K-1): |
---|
971 | dflux_s(i) = zx_nh(i) |
---|
972 | dflux_l(i) = (zx_sl(i) * zx_nq(i)) |
---|
973 | ENDDO |
---|
974 | |
---|
975 | END SUBROUTINE calcul_fluxs |
---|
976 | ! |
---|
977 | !######################################################################### |
---|
978 | ! |
---|
979 | |
---|
980 | END MODULE interface_surf |
---|