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

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

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

revision 301 by guez, Thu Aug 2 17:23:07 2018 UTC revision 311 by guez, Mon Dec 3 17:52:21 2018 UTC
# Line 4  module interfsurf_hq_m Line 4  module interfsurf_hq_m
4    
5  contains  contains
6    
7    SUBROUTINE interfsurf_hq(julien, mu0, nisurf, knindex, tsoil, qsol, u1_lay, &    SUBROUTINE interfsurf_hq(julien, mu0, nisurf, knindex, tsoil, qsol, u1lay, &
8         v1_lay, temp_air, spechum, tq_cdrag, tAcoef, qAcoef, tBcoef, qBcoef, &         v1lay, temp_air, q1lay, cdragh, tAcoef, qAcoef, tBcoef, qBcoef, &
9         precip_rain, precip_snow, rugos, rugoro, snow, qsurf, ts, p1lay, ps, &         rain_fall, snow_fall, rugos, rugoro, snow, qsurf, ts, p1lay, ps, &
10         radsol, evap, flux_t, fluxlat, dflux_l, dflux_s, tsurf_new, albedo, &         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, &         z0_new, pctsrf_new_sic, agesno, fqcalving, ffonte, run_off_lic_0, &
12         run_off_lic)         run_off_lic)
# Line 40  contains Line 40  contains
40      REAL, intent(INOUT):: qsol(:) ! (knon)      REAL, intent(INOUT):: qsol(:) ! (knon)
41      ! column-density of water in soil, in kg m-2      ! column-density of water in soil, in kg m-2
42    
43      real, intent(IN):: u1_lay(:), v1_lay(:) ! (knon) vitesse 1ere couche      real, intent(IN):: u1lay(:), v1lay(:) ! (knon) vitesse 1ere couche
44    
45      real, intent(IN):: temp_air(:) ! (knon) temperature de l'air 1ere couche      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      real, intent(IN):: q1lay(:) ! (knon)
48        ! humidit\'e sp\'ecifique de la premi\`ere couche
49    
50        real, intent(IN):: cdragh(:) ! (knon) coefficient d'echange
51    
52      real, intent(IN):: tAcoef(:), qAcoef(:) ! (knon)      real, intent(IN):: tAcoef(:), qAcoef(:) ! (knon)
53      ! coefficients A de la r\'esolution de la couche limite pour t et q      ! coefficients A de la r\'esolution de la couche limite pour t et q
# Line 52  contains Line 55  contains
55      real, intent(IN):: tBcoef(:), qBcoef(:) ! (knon)      real, intent(IN):: tBcoef(:), qBcoef(:) ! (knon)
56      ! coefficients B de la r\'esolution de la couche limite pour t et q      ! coefficients B de la r\'esolution de la couche limite pour t et q
57    
58      real, intent(IN):: precip_rain(:) ! (knon)      real, intent(IN):: rain_fall(:) ! (knon)
59      ! precipitation, liquid water mass flux (kg / m2 / s), positive down      ! precipitation, liquid water mass flux (kg / m2 / s), positive down
60    
61      real, intent(IN):: precip_snow(:) ! (knon)      real, intent(IN):: snow_fall(:) ! (knon)
62      ! precipitation, solid water mass flux (kg / m2 / s), positive down      ! precipitation, solid water mass flux (kg / m2 / s), positive down
63    
64      real, intent(IN):: rugos(:) ! (knon) rugosite      real, intent(IN):: rugos(:) ! (knon) rugosite
# Line 64  contains Line 67  contains
67      real, intent(OUT):: qsurf(:) ! (knon)      real, intent(OUT):: qsurf(:) ! (knon)
68      real, intent(IN):: ts(:) ! (knon) temp\'erature de surface      real, intent(IN):: ts(:) ! (knon) temp\'erature de surface
69      real, intent(IN):: p1lay(:) ! (knon) pression 1er niveau (milieu de couche)      real, intent(IN):: p1lay(:) ! (knon) pression 1er niveau (milieu de couche)
70      real, intent(IN):: ps(:) ! (knon) pression au sol      real, intent(IN):: ps(:) ! (knon) pression au sol, en Pa
71      REAL, INTENT(IN):: radsol(:) ! (knon) rayonnement net au sol (LW + SW)  
72        REAL, INTENT(IN):: radsol(:) ! (knon)
73        ! surface net downward radiative flux, in W / m2
74    
75      real, intent(OUT):: evap(:) ! (knon) evaporation totale      real, intent(OUT):: evap(:) ! (knon) evaporation totale
76    
77      real, intent(OUT):: flux_t(:) ! (knon) flux de chaleur sensible      real, intent(OUT):: flux_t(:) ! (knon) flux de chaleur sensible
78      ! (Cp T) à la surface, positif vers le bas, W / m2      ! (Cp T) à la surface, positif vers le bas, W / m2
79    
80      real, intent(OUT):: fluxlat(:) ! (knon) flux de chaleur latente      real, intent(OUT):: fluxlat(:) ! (knon) flux de chaleur latente, en W m-2
81      real, intent(OUT):: dflux_l(:), dflux_s(:) ! (knon)      real, intent(OUT):: dflux_l(:), dflux_s(:) ! (knon)
82      real, intent(OUT):: tsurf_new(:) ! (knon) temp\'erature au sol      real, intent(OUT):: tsurf_new(:) ! (knon) temp\'erature au sol
83      real, intent(OUT):: albedo(:) ! (knon) albedo      real, intent(OUT):: albedo(:) ! (knon) albedo
# Line 124  contains Line 130  contains
130         CALL soil(is_ter, snow, ts, tsoil, soilcap, soilflux)         CALL soil(is_ter, snow, ts, tsoil, soilcap, soilflux)
131         cal = RCPD / soilcap         cal = RCPD / soilcap
132    
133         CALL calcul_fluxs(ts, p1lay, cal, beta, tq_cdrag, ps, qsurf, &         CALL calcul_fluxs(ts, p1lay, cal, beta, cdragh, ps, qsurf, &
134              radsol + soilflux, temp_air, spechum, u1_lay, v1_lay, tAcoef, &              radsol + soilflux, temp_air, q1lay, u1lay, v1lay, tAcoef, &
135              qAcoef, tBcoef, qBcoef, tsurf_new, evap, fluxlat, flux_t, dflux_s, &              qAcoef, tBcoef, qBcoef, tsurf_new, evap, fluxlat, flux_t, dflux_s, &
136              dflux_l, dif_grnd = 0.)              dflux_l, dif_grnd = 0.)
137         CALL fonte_neige(is_ter, precip_rain, precip_snow, snow, qsol, &         CALL fonte_neige(is_ter, rain_fall, snow_fall, snow, qsol, &
138              tsurf_new, evap, fqcalving, ffonte, run_off_lic_0, run_off_lic)              tsurf_new, evap, fqcalving, ffonte, run_off_lic_0, run_off_lic)
139    
140         call albsno(agesno, alb_neig, precip_snow)         call albsno(agesno, alb_neig, snow_fall)
141         where (snow < 0.0001) agesno = 0.         where (snow < 0.0001) agesno = 0.
142         zfra = max(0., min(1., snow / (snow + 10.)))         zfra = max(0., min(1., snow / (snow + 10.)))
143         albedo = alb_neig * zfra + albedo * (1. - zfra)         albedo = alb_neig * zfra + albedo * (1. - zfra)
# Line 143  contains Line 149  contains
149         call limit_read_sst(julien, knindex, tsurf)         call limit_read_sst(julien, knindex, tsurf)
150         cal = 0.         cal = 0.
151         beta = 1.         beta = 1.
152         call calcul_fluxs(tsurf, p1lay, cal, beta, tq_cdrag, ps, qsurf, radsol, &         call calcul_fluxs(tsurf, p1lay, cal, beta, cdragh, ps, qsurf, radsol, &
153              temp_air, spechum, u1_lay, v1_lay, tAcoef, qAcoef, tBcoef, qBcoef, &              temp_air, q1lay, u1lay, v1lay, tAcoef, qAcoef, tBcoef, qBcoef, &
154              tsurf_new, evap, fluxlat, flux_t, dflux_s, dflux_l, dif_grnd = 0.)              tsurf_new, evap, fluxlat, flux_t, dflux_s, dflux_l, dif_grnd = 0.)
155         agesno = 0.         agesno = 0.
156         albedo = alboc_cd(mu0) * fmagic         albedo = alboc_cd(mu0) * fmagic
# Line 167  contains Line 173  contains
173         cal = RCPD / soilcap         cal = RCPD / soilcap
174         tsurf = tsurf_new         tsurf = tsurf_new
175         beta = 1.         beta = 1.
176         CALL calcul_fluxs(tsurf, p1lay, cal, beta, tq_cdrag, ps, qsurf, &         CALL calcul_fluxs(tsurf, p1lay, cal, beta, cdragh, ps, qsurf, &
177              radsol + soilflux, temp_air, spechum, u1_lay, v1_lay, tAcoef, &              radsol + soilflux, temp_air, q1lay, u1lay, v1lay, tAcoef, &
178              qAcoef, tBcoef, qBcoef, tsurf_new, evap, fluxlat, flux_t, dflux_s, &              qAcoef, tBcoef, qBcoef, tsurf_new, evap, fluxlat, flux_t, dflux_s, &
179              dflux_l, dif_grnd = 1. / tau_gl)              dflux_l, dif_grnd = 1. / tau_gl)
180         CALL fonte_neige(is_sic, precip_rain, precip_snow, snow, qsol, &         CALL fonte_neige(is_sic, rain_fall, snow_fall, snow, qsol, &
181              tsurf_new, evap, fqcalving, ffonte, run_off_lic_0, run_off_lic)              tsurf_new, evap, fqcalving, ffonte, run_off_lic_0, run_off_lic)
182    
183         ! Compute the albedo:         ! Compute the albedo:
184    
185         CALL albsno(agesno, alb_neig, precip_snow)         CALL albsno(agesno, alb_neig, snow_fall)
186         WHERE (snow < 0.0001) agesno = 0.         WHERE (snow < 0.0001) agesno = 0.
187         zfra = MAX(0., MIN(1., snow / (snow + 10.)))         zfra = MAX(0., MIN(1., snow / (snow + 10.)))
188         albedo = alb_neig * zfra + 0.6 * (1. - zfra)         albedo = alb_neig * zfra + 0.6 * (1. - zfra)
# Line 188  contains Line 194  contains
194         CALL soil(is_lic, snow, ts, tsoil, soilcap, soilflux)         CALL soil(is_lic, snow, ts, tsoil, soilcap, soilflux)
195         cal = RCPD / soilcap         cal = RCPD / soilcap
196         beta = 1.         beta = 1.
197         call calcul_fluxs(ts, p1lay, cal, beta, tq_cdrag, ps, qsurf, &         call calcul_fluxs(ts, p1lay, cal, beta, cdragh, ps, qsurf, &
198              radsol + soilflux, temp_air, spechum, u1_lay, v1_lay, tAcoef, &              radsol + soilflux, temp_air, q1lay, u1lay, v1lay, tAcoef, &
199              qAcoef, tBcoef, qBcoef, tsurf_new, evap, fluxlat, flux_t, dflux_s, &              qAcoef, tBcoef, qBcoef, tsurf_new, evap, fluxlat, flux_t, dflux_s, &
200              dflux_l, dif_grnd = 0.)              dflux_l, dif_grnd = 0.)
201         call fonte_neige(is_lic, precip_rain, precip_snow, snow, qsol, &         call fonte_neige(is_lic, rain_fall, snow_fall, snow, qsol, &
202              tsurf_new, evap, fqcalving, ffonte, run_off_lic_0, run_off_lic)              tsurf_new, evap, fqcalving, ffonte, run_off_lic_0, run_off_lic)
203    
204         ! calcul albedo         ! calcul albedo
205         CALL albsno(agesno, alb_neig, precip_snow)         CALL albsno(agesno, alb_neig, snow_fall)
206         WHERE (snow < 0.0001) agesno = 0.         WHERE (snow < 0.0001) agesno = 0.
207         albedo = 0.77         albedo = 0.77
208    

Legend:
Removed from v.301  
changed lines
  Added in v.311

  ViewVC Help
Powered by ViewVC 1.1.21