/[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 206 by guez, Tue Aug 30 12:52:46 2016 UTC revision 209 by guez, Wed Dec 7 17:37:21 2016 UTC
# Line 4  module interfsurf_hq_m Line 4  module interfsurf_hq_m
4    
5  contains  contains
6    
7    SUBROUTINE interfsurf_hq(dtime, jour, rmu0, nisurf, knon, knindex, rlat, &    SUBROUTINE interfsurf_hq(dtime, jour, rmu0, nisurf, knon, knindex, debut, &
8         debut, nsoilmx, tsoil, qsol, u1_lay, v1_lay, temp_air, spechum, &         tsoil, qsol, u1_lay, v1_lay, temp_air, spechum, tq_cdrag, petAcoef, &
9         tq_cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, precip_rain, &         peqAcoef, petBcoef, peqBcoef, precip_rain, precip_snow, fder, rugos, &
10         precip_snow, fder, rugos, rugoro, snow, qsurf, tsurf, p1lay, ps, &         rugoro, snow, qsurf, tsurf, p1lay, ps, radsol, evap, flux_t, fluxlat, &
11         radsol, evap, flux_t, fluxlat, dflux_l, dflux_s, tsurf_new, albedo, &         dflux_l, dflux_s, tsurf_new, albedo, z0_new, pctsrf_new_sic, agesno, &
12         z0_new, pctsrf_new_sic, agesno, fqcalving, ffonte, run_off_lic_0)         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 19  contains Line 19  contains
19    
20      USE abort_gcm_m, ONLY: abort_gcm      USE abort_gcm_m, ONLY: abort_gcm
21      use alboc_cd_m, only: alboc_cd      use alboc_cd_m, only: alboc_cd
     use alboc_m, only: alboc  
22      USE albsno_m, ONLY: albsno      USE albsno_m, ONLY: albsno
23      use calbeta_m, only: calbeta      use calbeta_m, only: calbeta
24      USE calcul_fluxs_m, ONLY: calcul_fluxs      USE calcul_fluxs_m, ONLY: calcul_fluxs
25      use clesphys2, only: soil_model, cycle_diurne      use clesphys2, only: soil_model
26      USE dimphy, ONLY: klon      USE dimphy, ONLY: klon
27      USE fonte_neige_m, ONLY: fonte_neige      USE fonte_neige_m, ONLY: fonte_neige
28      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
29      USE interface_surf, ONLY: run_off_lic, conf_interface      USE interface_surf, ONLY: run_off_lic, conf_interface
30      USE interfsur_lim_m, ONLY: interfsur_lim      USE interfsur_lim_m, ONLY: interfsur_lim
31      use read_sst_m, only: read_sst      use read_sst_m, only: read_sst
# Line 42  contains Line 41  contains
41      integer, intent(in):: knindex(:) ! (knon)      integer, intent(in):: knindex(:) ! (knon)
42      ! index des points de la surface a traiter      ! index des points de la surface a traiter
43    
     real, intent(IN):: rlat(klon) ! latitudes  
   
44      logical, intent(IN):: debut ! 1er appel a la physique      logical, intent(IN):: debut ! 1er appel a la physique
45      ! (si false calcul simplifie des fluxs sur les continents)      ! (si false calcul simplifie des fluxs sur les continents)
46    
47      integer, intent(in):: nsoilmx      REAL, intent(inout):: tsoil(:, :) ! (knon, nsoilmx)
     REAL tsoil(klon, nsoilmx)  
48    
49      REAL, intent(INOUT):: qsol(klon)      REAL, intent(INOUT):: qsol(klon)
50      ! column-density of water in soil, in kg m-2      ! column-density of water in soil, in kg m-2
# Line 91  contains Line 87  contains
87      real, intent(OUT):: flux_t(:) ! (knon) flux de chaleur sensible      real, intent(OUT):: flux_t(:) ! (knon) flux de chaleur sensible
88      real, dimension(klon), intent(OUT):: fluxlat ! flux de chaleur latente      real, dimension(klon), intent(OUT):: fluxlat ! flux de chaleur latente
89      real, dimension(klon), intent(OUT):: dflux_l, dflux_s      real, dimension(klon), intent(OUT):: dflux_l, dflux_s
90      real, intent(OUT):: tsurf_new(knon) ! temp\'erature au sol      real, intent(OUT):: tsurf_new(:) ! (knon) temp\'erature au sol
91      real, intent(OUT):: albedo(:) ! (knon) albedo      real, intent(OUT):: albedo(:) ! (knon) albedo
92      real, intent(OUT):: z0_new(klon) ! surface roughness      real, intent(OUT):: z0_new(klon) ! surface roughness
93    
# Line 113  contains Line 109  contains
109      ! run_off_lic_0 runoff glacier du pas de temps precedent      ! run_off_lic_0 runoff glacier du pas de temps precedent
110    
111      ! Local:      ! Local:
112      REAL soilcap(klon)      REAL soilcap(knon)
113      REAL soilflux(klon)      REAL soilflux(knon)
114      logical:: first_call = .true.      logical:: first_call = .true.
115      integer ii      integer ii
116      real, dimension(klon):: cal, beta, dif_grnd, capsol      real, dimension(klon):: cal, beta, dif_grnd, capsol
# Line 123  contains Line 119  contains
119      real tsurf_temp(knon)      real tsurf_temp(knon)
120      real alb_neig(knon)      real alb_neig(knon)
121      real zfra(knon)      real zfra(knon)
122        REAL, PARAMETER:: fmagic = 1. ! facteur magique pour r\'egler l'alb\'edo
123    
124      !-------------------------------------------------------------      !-------------------------------------------------------------
125    
# Line 142  contains Line 139  contains
139         if (is_oce > is_sic) then         if (is_oce > is_sic) then
140            print *, 'is_oce = ', is_oce, '> is_sic = ', is_sic            print *, 'is_oce = ', is_oce, '> is_sic = ', is_sic
141            call abort_gcm("interfsurf_hq", &            call abort_gcm("interfsurf_hq", &
142                 'L''ocean doit etre traite avant la banquise')                 "L'ocean doit etre traite avant la banquise")
143         endif         endif
144    
145         first_call = .false.         first_call = .false.
# Line 177  contains Line 174  contains
174              capsol(:knon), dif_grnd(:knon))              capsol(:knon), dif_grnd(:knon))
175    
176         IF (soil_model) THEN         IF (soil_model) THEN
177            CALL soil(dtime, is_ter, knon, snow, tsurf, tsoil, soilcap, soilflux)            CALL soil(dtime, is_ter, snow(:knon), tsurf, tsoil, soilcap, soilflux)
178            cal(1:knon) = RCPD / soilcap(1:knon)            cal(1:knon) = RCPD / soilcap
179            radsol(1:knon) = radsol(1:knon) + soilflux(:knon)            radsol(1:knon) = radsol(1:knon) + soilflux
180         ELSE         ELSE
181            cal = RCPD * capsol            cal = RCPD * capsol
182         ENDIF         ENDIF
# Line 207  contains Line 204  contains
204         ! Surface "oc\'ean", appel \`a l'interface avec l'oc\'ean         ! Surface "oc\'ean", appel \`a l'interface avec l'oc\'ean
205    
206         call read_sst(dtime, jour, knindex, debut, tsurf_temp)         call read_sst(dtime, jour, knindex, debut, tsurf_temp)
   
207         cal = 0.         cal = 0.
208         beta = 1.         beta = 1.
209         dif_grnd = 0.         dif_grnd = 0.
# Line 219  contains Line 215  contains
215              petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap, &              petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap, &
216              fluxlat(:knon), flux_t, dflux_s(:knon), dflux_l(:knon))              fluxlat(:knon), flux_t, dflux_s(:knon), dflux_l(:knon))
217         fder = fder + dflux_s + dflux_l         fder = fder + dflux_s + dflux_l
218           albedo = alboc_cd(rmu0(knindex)) * fmagic
        ! Compute the albedo:  
        if (cycle_diurne) then  
           CALL alboc_cd(rmu0(knindex), albedo)  
        else  
           CALL alboc(jour, rlat(knindex), albedo)  
        endif  
   
219         z0_new = sqrt(rugos**2 + rugoro**2)         z0_new = sqrt(rugos**2 + rugoro**2)
220      case (is_sic)      case (is_sic)
221         ! 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 233  contains
233              capsol(:knon), dif_grnd(:knon))              capsol(:knon), dif_grnd(:knon))
234    
235         IF (soil_model) THEN         IF (soil_model) THEN
236            CALL soil(dtime, is_sic, knon, snow, tsurf_new, tsoil, soilcap, &            CALL soil(dtime, is_sic, snow(:knon), tsurf_new, tsoil, soilcap, &
237                 soilflux)                 soilflux)
238            cal(1:knon) = RCPD / soilcap(1:knon)            cal(1:knon) = RCPD / soilcap
239            radsol(1:knon) = radsol(1:knon) + soilflux(1:knon)            radsol(1:knon) = radsol(1:knon) + soilflux
240            dif_grnd = 0.            dif_grnd = 0.
241         ELSE         ELSE
242            dif_grnd = 1. / tau_gl            dif_grnd = 1. / tau_gl
# Line 289  contains Line 278  contains
278         ! Surface "glacier continentaux" appel a l'interface avec le sol         ! Surface "glacier continentaux" appel a l'interface avec le sol
279    
280         IF (soil_model) THEN         IF (soil_model) THEN
281            CALL soil(dtime, is_lic, knon, snow, tsurf, tsoil, soilcap, soilflux)            CALL soil(dtime, is_lic, snow(:knon), tsurf, tsoil, soilcap, soilflux)
282            cal(1:knon) = RCPD / soilcap(1:knon)            cal(1:knon) = RCPD / soilcap
283            radsol(1:knon) = radsol(1:knon) + soilflux(1:knon)            radsol(1:knon) = radsol(1:knon) + soilflux
284         ELSE         ELSE
285            cal = RCPD * calice            cal = RCPD * calice
286            WHERE (snow > 0.) cal = RCPD * calsno            WHERE (snow > 0.) cal = RCPD * calsno

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

  ViewVC Help
Powered by ViewVC 1.1.21