/[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 175 by guez, Fri Feb 5 16:02:34 2016 UTC revision 202 by guez, Wed Jun 8 12:23:41 2016 UTC
# Line 4  module interfsurf_hq_m Line 4  module interfsurf_hq_m
4    
5  contains  contains
6    
7    SUBROUTINE interfsurf_hq(itime, dtime, jour, rmu0, nisurf, knon, knindex, &    SUBROUTINE interfsurf_hq(dtime, jour, rmu0, nisurf, knon, knindex, rlat, &
8         pctsrf, rlat, debut, nsoilmx, tsoil, qsol, u1_lay, v1_lay, temp_air, &         debut, nsoilmx, tsoil, qsol, u1_lay, v1_lay, temp_air, spechum, &
9         spechum, tq_cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, &         tq_cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, precip_rain, &
10         precip_rain, precip_snow, fder, rugos, rugoro, snow, qsurf, tsurf, &         precip_snow, fder, rugos, rugoro, snow, qsurf, tsurf, p1lay, ps, &
11         p1lay, ps, radsol, evap, fluxsens, fluxlat, dflux_l, dflux_s, &         radsol, evap, fluxsens, fluxlat, dflux_l, dflux_s, tsurf_new, albedo, &
12         tsurf_new, albedo, z0_new, pctsrf_new, agesno, fqcalving, ffonte, &         z0_new, pctsrf_new_sic, agesno, fqcalving, ffonte, run_off_lic_0)
        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 28  contains Line 27  contains
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, nbsrf
30      USE interface_surf, ONLY: run_off, run_off_lic, conf_interface      USE interface_surf, ONLY: run_off_lic, conf_interface
     USE interfoce_lim_m, ONLY: interfoce_lim  
31      USE interfsur_lim_m, ONLY: interfsur_lim      USE interfsur_lim_m, ONLY: interfsur_lim
32        use read_sst_m, only: read_sst
33      use soil_m, only: soil      use soil_m, only: soil
34      USE suphec_m, ONLY: rcpd, rlstt, rlvtt, rtt      USE suphec_m, ONLY: rcpd, rtt
35    
     integer, intent(IN):: itime ! numero du pas de temps  
36      real, intent(IN):: dtime ! pas de temps de la physique (en s)      real, intent(IN):: dtime ! pas de temps de la physique (en s)
37      integer, intent(IN):: jour ! jour dans l'annee en cours      integer, intent(IN):: jour ! jour dans l'annee en cours
38      real, intent(IN):: rmu0(klon) ! cosinus de l'angle solaire zenithal      real, intent(IN):: rmu0(klon) ! cosinus de l'angle solaire zenithal
# Line 44  contains Line 42  contains
42      integer, intent(in):: knindex(:) ! (knon)      integer, intent(in):: knindex(:) ! (knon)
43      ! index des points de la surface a traiter      ! index des points de la surface a traiter
44    
     real, intent(IN):: pctsrf(klon, nbsrf)  
     ! tableau des pourcentages de surface de chaque maille  
   
45      real, intent(IN):: rlat(klon) ! latitudes      real, intent(IN):: rlat(klon) ! latitudes
46    
47      logical, intent(IN):: debut ! 1er appel a la physique      logical, intent(IN):: debut ! 1er appel a la physique
# Line 100  contains Line 95  contains
95      real, intent(OUT):: tsurf_new(knon) ! temp\'erature au sol      real, intent(OUT):: tsurf_new(knon) ! temp\'erature au sol
96      real, intent(OUT):: albedo(:) ! (knon) albedo      real, intent(OUT):: albedo(:) ! (knon) albedo
97      real, intent(OUT):: z0_new(klon) ! surface roughness      real, intent(OUT):: z0_new(klon) ! surface roughness
98      real, dimension(klon, nbsrf), intent(OUT):: pctsrf_new  
99      ! pctsrf_new nouvelle repartition des surfaces      real, intent(in):: pctsrf_new_sic(:) ! (klon)
100        ! nouvelle repartition des surfaces
101    
102      real, intent(INOUT):: agesno(:) ! (knon)      real, intent(INOUT):: agesno(:) ! (knon)
103    
104      ! Flux d'eau "perdue" par la surface et n\'ecessaire pour que limiter la      ! Flux d'eau "perdue" par la surface et n\'ecessaire pour que limiter la
# Line 169  contains Line 166  contains
166      case (is_ter)      case (is_ter)
167         ! Surface "terre", appel \`a l'interface avec les sols continentaux         ! Surface "terre", appel \`a l'interface avec les sols continentaux
168    
        ! allocation du run-off  
        if (.not. allocated(run_off)) then  
           allocate(run_off(knon))  
           run_off = 0.  
        else if (size(run_off) /= knon) then  
           call abort_gcm("interfsurf_hq", 'Something is wrong: the number of ' &  
                // 'continental points has changed since last call.')  
        endif  
   
169         ! Calcul age de la neige         ! Calcul age de la neige
170    
171         ! Read albedo from the file containing boundary conditions then         ! Read albedo from the file containing boundary conditions then
172         ! add the albedo of snow:         ! add the albedo of snow:
173    
174         call interfsur_lim(itime, dtime, jour, knindex, debut, albedo, z0_new)         call interfsur_lim(dtime, jour, knindex, debut, albedo, z0_new)
175    
176         ! Calcul snow et qsurf, hydrologie adapt\'ee         ! Calcul snow et qsurf, hydrologie adapt\'ee
177         CALL calbeta(nisurf, snow(:knon), qsol(:knon), beta(:knon), &         CALL calbeta(is_ter, snow(:knon), qsol(:knon), beta(:knon), &
178              capsol(:knon), dif_grnd(:knon))              capsol(:knon), dif_grnd(:knon))
179    
180         IF (soil_model) THEN         IF (soil_model) THEN
181            CALL soil(dtime, nisurf, knon, snow, tsurf, tsoil, soilcap, soilflux)            CALL soil(dtime, is_ter, knon, snow, tsurf, tsoil, soilcap, soilflux)
182            cal(1:knon) = RCPD / soilcap(1:knon)            cal(1:knon) = RCPD / soilcap(1:knon)
183            radsol(1:knon) = radsol(1:knon) + soilflux(:knon)            radsol(1:knon) = radsol(1:knon) + soilflux(:knon)
184         ELSE         ELSE
# Line 204  contains Line 192  contains
192              petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap(:knon), &              petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap(:knon), &
193              fluxlat(:knon), fluxsens(:knon), dflux_s(:knon), dflux_l(:knon))              fluxlat(:knon), fluxsens(:knon), dflux_s(:knon), dflux_l(:knon))
194    
195         CALL fonte_neige(nisurf, dtime, tsurf, p1lay(:knon), beta(:knon), &         CALL fonte_neige(is_ter, dtime, tsurf, p1lay(:knon), beta(:knon), &
196              tq_cdrag(:knon), ps(:knon), precip_rain(:knon), &              tq_cdrag(:knon), ps(:knon), precip_rain(:knon), &
197              precip_snow(:knon), snow(:knon), qsol(:knon), temp_air(:knon), &              precip_snow(:knon), snow(:knon), qsol(:knon), temp_air(:knon), &
198              spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), &              spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), &
# Line 216  contains Line 204  contains
204         zfra = max(0., min(1., snow(:knon) / (snow(:knon) + 10.)))         zfra = max(0., min(1., snow(:knon) / (snow(:knon) + 10.)))
205         albedo = alb_neig * zfra + albedo * (1. - zfra)         albedo = alb_neig * zfra + albedo * (1. - zfra)
206         z0_new = sqrt(z0_new**2 + rugoro**2)         z0_new = sqrt(z0_new**2 + rugoro**2)
   
        ! Remplissage des pourcentages de surface  
        pctsrf_new(:, nisurf) = pctsrf(:, nisurf)  
207      case (is_oce)      case (is_oce)
208         ! Surface "oc\'ean", appel \`a l'interface avec l'oc\'ean         ! Surface "oc\'ean", appel \`a l'interface avec l'oc\'ean
209    
210         call interfoce_lim(itime, dtime, jour, knindex, debut, tsurf_temp, &         call read_sst(dtime, jour, knindex, debut, tsurf_temp)
             pctsrf_new)  
211    
212         cal = 0.         cal = 0.
213         beta = 1.         beta = 1.
# Line 248  contains Line 232  contains
232      case (is_sic)      case (is_sic)
233         ! Surface "glace de mer" appel a l'interface avec l'ocean         ! Surface "glace de mer" appel a l'interface avec l'ocean
234    
        ! ! lecture conditions limites  
        CALL interfoce_lim(itime, dtime, jour, knindex, debut, tsurf_new, &  
             pctsrf_new)  
   
235         DO ii = 1, knon         DO ii = 1, knon
236            tsurf_new(ii) = tsurf(ii)            tsurf_new(ii) = tsurf(ii)
237            IF (pctsrf_new(knindex(ii), nisurf) < EPSFRA) then            IF (pctsrf_new_sic(knindex(ii)) < EPSFRA) then
238               snow(ii) = 0.               snow(ii) = 0.
239               tsurf_new(ii) = RTT - 1.8               tsurf_new(ii) = RTT - 1.8
240               IF (soil_model) tsoil(ii, :) = RTT - 1.8               IF (soil_model) tsoil(ii, :) = RTT - 1.8
241            endif            endif
242         enddo         enddo
243    
244         CALL calbeta(nisurf, snow(:knon), qsol(:knon), beta(:knon), &         CALL calbeta(is_sic, snow(:knon), qsol(:knon), beta(:knon), &
245              capsol(:knon), dif_grnd(:knon))              capsol(:knon), dif_grnd(:knon))
246    
247         IF (soil_model) THEN         IF (soil_model) THEN
248            CALL soil(dtime, nisurf, knon, snow, tsurf_new, tsoil, soilcap, &            CALL soil(dtime, is_sic, knon, snow, tsurf_new, tsoil, soilcap, &
249                 soilflux)                 soilflux)
250            cal(1:knon) = RCPD / soilcap(1:knon)            cal(1:knon) = RCPD / soilcap(1:knon)
251            radsol(1:knon) = radsol(1:knon) + soilflux(1:knon)            radsol(1:knon) = radsol(1:knon) + soilflux(1:knon)
# Line 285  contains Line 265  contains
265              petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap(:knon), &              petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap(:knon), &
266              fluxlat(:knon), fluxsens(:knon), dflux_s(:knon), dflux_l(:knon))              fluxlat(:knon), fluxsens(:knon), dflux_s(:knon), dflux_l(:knon))
267    
268         CALL fonte_neige(nisurf, dtime, tsurf_temp, p1lay(:knon), beta(:knon), &         CALL fonte_neige(is_sic, dtime, tsurf_temp, p1lay(:knon), beta(:knon), &
269              tq_cdrag(:knon), ps(:knon), precip_rain(:knon), &              tq_cdrag(:knon), ps(:knon), precip_rain(:knon), &
270              precip_snow(:knon), snow(:knon), qsol(:knon), temp_air(:knon), &              precip_snow(:knon), snow(:knon), qsol(:knon), temp_air(:knon), &
271              spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), &              spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), &
# Line 300  contains Line 280  contains
280         albedo = alb_neig * zfra + 0.6 * (1. - zfra)         albedo = alb_neig * zfra + 0.6 * (1. - zfra)
281    
282         fder = fder + dflux_s + dflux_l         fder = fder + dflux_s + dflux_l
283           z0_new = SQRT(0.002**2 + rugoro**2)
        ! 2eme appel a interfoce pour le cumul et le passage des flux a l'ocean  
   
        z0_new = 0.002  
        z0_new = SQRT(z0_new**2 + rugoro**2)  
284      case (is_lic)      case (is_lic)
285         if (.not. allocated(run_off_lic)) then         if (.not. allocated(run_off_lic)) then
286            allocate(run_off_lic(knon))            allocate(run_off_lic(knon))
# Line 314  contains Line 290  contains
290         ! Surface "glacier continentaux" appel a l'interface avec le sol         ! Surface "glacier continentaux" appel a l'interface avec le sol
291    
292         IF (soil_model) THEN         IF (soil_model) THEN
293            CALL soil(dtime, nisurf, knon, snow, tsurf, tsoil, soilcap, soilflux)            CALL soil(dtime, is_lic, knon, snow, tsurf, tsoil, soilcap, soilflux)
294            cal(1:knon) = RCPD / soilcap(1:knon)            cal(1:knon) = RCPD / soilcap(1:knon)
295            radsol(1:knon) = radsol(1:knon) + soilflux(1:knon)            radsol(1:knon) = radsol(1:knon) + soilflux(1:knon)
296         ELSE         ELSE
# Line 331  contains Line 307  contains
307              petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap(:knon), &              petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap(:knon), &
308              fluxlat(:knon), fluxsens(:knon), dflux_s(:knon), dflux_l(:knon))              fluxlat(:knon), fluxsens(:knon), dflux_s(:knon), dflux_l(:knon))
309    
310         call fonte_neige(nisurf, dtime, tsurf, p1lay(:knon), beta(:knon), &         call fonte_neige(is_lic, dtime, tsurf, p1lay(:knon), beta(:knon), &
311              tq_cdrag(:knon), ps(:knon), precip_rain(:knon), &              tq_cdrag(:knon), ps(:knon), precip_rain(:knon), &
312              precip_snow(:knon), snow(:knon), qsol(:knon), temp_air(:knon), &              precip_snow(:knon), snow(:knon), qsol(:knon), temp_air(:knon), &
313              spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), &              spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), &
# Line 345  contains Line 321  contains
321    
322         ! Rugosite         ! Rugosite
323         z0_new = rugoro         z0_new = rugoro
   
        ! Remplissage des pourcentages de surface  
        pctsrf_new(:, nisurf) = pctsrf(:, nisurf)  
   
324      case default      case default
325         print *, 'Index surface = ', nisurf         print *, 'Index surface = ', nisurf
326         call abort_gcm("interfsurf_hq", 'Index surface non valable')         call abort_gcm("interfsurf_hq", 'Index surface non valable')

Legend:
Removed from v.175  
changed lines
  Added in v.202

  ViewVC Help
Powered by ViewVC 1.1.21