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

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

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

revision 206 by guez, Tue Aug 30 12:52:46 2016 UTC revision 208 by guez, Wed Dec 7 16:44:53 2016 UTC
# Line 5  module interfsurf_hq_m Line 5  module interfsurf_hq_m
5  contains  contains
6    
7    SUBROUTINE interfsurf_hq(dtime, jour, rmu0, nisurf, knon, knindex, rlat, &    SUBROUTINE interfsurf_hq(dtime, jour, rmu0, nisurf, knon, knindex, rlat, &
8         debut, nsoilmx, tsoil, qsol, u1_lay, v1_lay, temp_air, spechum, &         debut, tsoil, qsol, u1_lay, v1_lay, temp_air, spechum, tq_cdrag, &
9         tq_cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, precip_rain, &         petAcoef, peqAcoef, petBcoef, peqBcoef, precip_rain, precip_snow, &
10         precip_snow, fder, rugos, rugoro, snow, qsurf, tsurf, p1lay, ps, &         fder, rugos, rugoro, snow, qsurf, tsurf, p1lay, ps, radsol, evap, &
11         radsol, evap, flux_t, fluxlat, dflux_l, dflux_s, tsurf_new, albedo, &         flux_t, fluxlat, dflux_l, dflux_s, tsurf_new, albedo, z0_new, &
12         z0_new, pctsrf_new_sic, agesno, fqcalving, ffonte, run_off_lic_0)         pctsrf_new_sic, agesno, fqcalving, ffonte, run_off_lic_0)
13    
14      ! Cette routine sert d'aiguillage entre l'atmosph\`ere et la surface      ! 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      ! en g\'en\'eral (sols continentaux, oc\'eans, glaces) pour les flux de
# Line 26  contains Line 26  contains
26      use clesphys2, only: soil_model, cycle_diurne      use clesphys2, only: soil_model, cycle_diurne
27      USE dimphy, ONLY: klon      USE dimphy, ONLY: klon
28      USE fonte_neige_m, ONLY: fonte_neige      USE fonte_neige_m, ONLY: fonte_neige
29      USE indicesol, ONLY: epsfra, is_lic, is_oce, is_sic, is_ter, nbsrf      USE indicesol, ONLY: epsfra, is_lic, is_oce, is_sic, is_ter
30      USE interface_surf, ONLY: run_off_lic, conf_interface      USE interface_surf, ONLY: run_off_lic, conf_interface
31      USE interfsur_lim_m, ONLY: interfsur_lim      USE interfsur_lim_m, ONLY: interfsur_lim
32      use read_sst_m, only: read_sst      use read_sst_m, only: read_sst
# Line 47  contains Line 47  contains
47      logical, intent(IN):: debut ! 1er appel a la physique      logical, intent(IN):: debut ! 1er appel a la physique
48      ! (si false calcul simplifie des fluxs sur les continents)      ! (si false calcul simplifie des fluxs sur les continents)
49    
50      integer, intent(in):: nsoilmx      REAL, intent(inout):: tsoil(:, :) ! (knon, nsoilmx)
     REAL tsoil(klon, nsoilmx)  
51    
52      REAL, intent(INOUT):: qsol(klon)      REAL, intent(INOUT):: qsol(klon)
53      ! column-density of water in soil, in kg m-2      ! column-density of water in soil, in kg m-2
# Line 91  contains Line 90  contains
90      real, intent(OUT):: flux_t(:) ! (knon) flux de chaleur sensible      real, intent(OUT):: flux_t(:) ! (knon) flux de chaleur sensible
91      real, dimension(klon), intent(OUT):: fluxlat ! flux de chaleur latente      real, dimension(klon), intent(OUT):: fluxlat ! flux de chaleur latente
92      real, dimension(klon), intent(OUT):: dflux_l, dflux_s      real, dimension(klon), intent(OUT):: dflux_l, dflux_s
93      real, intent(OUT):: tsurf_new(knon) ! temp\'erature au sol      real, intent(OUT):: tsurf_new(:) ! (knon) temp\'erature au sol
94      real, intent(OUT):: albedo(:) ! (knon) albedo      real, intent(OUT):: albedo(:) ! (knon) albedo
95      real, intent(OUT):: z0_new(klon) ! surface roughness      real, intent(OUT):: z0_new(klon) ! surface roughness
96    
# Line 113  contains Line 112  contains
112      ! run_off_lic_0 runoff glacier du pas de temps precedent      ! run_off_lic_0 runoff glacier du pas de temps precedent
113    
114      ! Local:      ! Local:
115      REAL soilcap(klon)      REAL soilcap(knon)
116      REAL soilflux(klon)      REAL soilflux(knon)
117      logical:: first_call = .true.      logical:: first_call = .true.
118      integer ii      integer ii
119      real, dimension(klon):: cal, beta, dif_grnd, capsol      real, dimension(klon):: cal, beta, dif_grnd, capsol
# Line 123  contains Line 122  contains
122      real tsurf_temp(knon)      real tsurf_temp(knon)
123      real alb_neig(knon)      real alb_neig(knon)
124      real zfra(knon)      real zfra(knon)
125        REAL, PARAMETER:: fmagic = 1. ! facteur magique pour r\'egler l'alb\'edo
126    
127      !-------------------------------------------------------------      !-------------------------------------------------------------
128    
# Line 142  contains Line 142  contains
142         if (is_oce > is_sic) then         if (is_oce > is_sic) then
143            print *, 'is_oce = ', is_oce, '> is_sic = ', is_sic            print *, 'is_oce = ', is_oce, '> is_sic = ', is_sic
144            call abort_gcm("interfsurf_hq", &            call abort_gcm("interfsurf_hq", &
145                 'L''ocean doit etre traite avant la banquise')                 "L'ocean doit etre traite avant la banquise")
146         endif         endif
147    
148         first_call = .false.         first_call = .false.
# Line 177  contains Line 177  contains
177              capsol(:knon), dif_grnd(:knon))              capsol(:knon), dif_grnd(:knon))
178    
179         IF (soil_model) THEN         IF (soil_model) THEN
180            CALL soil(dtime, is_ter, knon, snow, tsurf, tsoil, soilcap, soilflux)            CALL soil(dtime, is_ter, snow(:knon), tsurf, tsoil, soilcap, soilflux)
181            cal(1:knon) = RCPD / soilcap(1:knon)            cal(1:knon) = RCPD / soilcap
182            radsol(1:knon) = radsol(1:knon) + soilflux(:knon)            radsol(1:knon) = radsol(1:knon) + soilflux
183         ELSE         ELSE
184            cal = RCPD * capsol            cal = RCPD * capsol
185         ENDIF         ENDIF
# Line 221  contains Line 221  contains
221         fder = fder + dflux_s + dflux_l         fder = fder + dflux_s + dflux_l
222    
223         ! Compute the albedo:         ! Compute the albedo:
224    
225         if (cycle_diurne) then         if (cycle_diurne) then
226            CALL alboc_cd(rmu0(knindex), albedo)            albedo = alboc_cd(rmu0(knindex))
227         else         else
228            CALL alboc(jour, rlat(knindex), albedo)            albedo = alboc(jour, rlat(knindex))
229         endif         endif
230    
231           albedo = albedo * fmagic
232    
233         z0_new = sqrt(rugos**2 + rugoro**2)         z0_new = sqrt(rugos**2 + rugoro**2)
234      case (is_sic)      case (is_sic)
235         ! Surface "glace de mer" appel a l'interface avec l'ocean         ! Surface "glace de mer" appel a l'interface avec l'ocean
# Line 244  contains Line 247  contains
247              capsol(:knon), dif_grnd(:knon))              capsol(:knon), dif_grnd(:knon))
248    
249         IF (soil_model) THEN         IF (soil_model) THEN
250            CALL soil(dtime, is_sic, knon, snow, tsurf_new, tsoil, soilcap, &            CALL soil(dtime, is_sic, snow(:knon), tsurf_new, tsoil, soilcap, &
251                 soilflux)                 soilflux)
252            cal(1:knon) = RCPD / soilcap(1:knon)            cal(1:knon) = RCPD / soilcap
253            radsol(1:knon) = radsol(1:knon) + soilflux(1:knon)            radsol(1:knon) = radsol(1:knon) + soilflux
254            dif_grnd = 0.            dif_grnd = 0.
255         ELSE         ELSE
256            dif_grnd = 1. / tau_gl            dif_grnd = 1. / tau_gl
# Line 289  contains Line 292  contains
292         ! Surface "glacier continentaux" appel a l'interface avec le sol         ! Surface "glacier continentaux" appel a l'interface avec le sol
293    
294         IF (soil_model) THEN         IF (soil_model) THEN
295            CALL soil(dtime, is_lic, knon, snow, tsurf, tsoil, soilcap, soilflux)            CALL soil(dtime, is_lic, snow(:knon), tsurf, tsoil, soilcap, soilflux)
296            cal(1:knon) = RCPD / soilcap(1:knon)            cal(1:knon) = RCPD / soilcap
297            radsol(1:knon) = radsol(1:knon) + soilflux(1:knon)            radsol(1:knon) = radsol(1:knon) + soilflux
298         ELSE         ELSE
299            cal = RCPD * calice            cal = RCPD * calice
300            WHERE (snow > 0.) cal = RCPD * calsno            WHERE (snow > 0.) cal = RCPD * calsno

Legend:
Removed from v.206  
changed lines
  Added in v.208

  ViewVC Help
Powered by ViewVC 1.1.21