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

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

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

revision 305 by guez, Tue Sep 11 11:08:38 2018 UTC revision 307 by guez, Tue Sep 11 12:52:28 2018 UTC
# Line 6  contains Line 6  contains
6    
7    SUBROUTINE pbl_surface(pctsrf, t, q, u, v, julien, mu0, ftsol, cdmmax, &    SUBROUTINE pbl_surface(pctsrf, t, q, u, v, julien, mu0, ftsol, cdmmax, &
8         cdhmax, ftsoil, qsol, paprs, pplay, fsnow, qsurf, falbe, fluxlat, &         cdhmax, ftsoil, qsol, paprs, pplay, fsnow, qsurf, falbe, fluxlat, &
9         rain_fall, snow_fall, fsolsw, fsollw, frugs, agesno, rugoro, d_t, d_q, &         rain_fall, snow_fall, frugs, agesno, rugoro, d_t, d_q, d_u, d_v, d_ts, &
10         d_u, d_v, d_ts, flux_t, flux_q, flux_u, flux_v, cdragh, cdragm, q2, &         flux_t, flux_q, flux_u, flux_v, cdragh, cdragm, q2, dflux_t, dflux_q, &
11         dflux_t, dflux_q, coefh, t2m, q2m, u10m_srf, v10m_srf, pblh, capcl, &         coefh, t2m, q2m, u10m_srf, v10m_srf, pblh, capcl, oliqcl, cteicl, pblt, &
12         oliqcl, cteicl, pblt, therm, plcl, fqcalving, ffonte, run_off_lic_0)         therm, plcl, fqcalving, ffonte, run_off_lic_0, albsol, sollw, solsw, &
13           tsol)
14    
15      ! From phylmd/clmain.F, version 1.6, 2005/11/16 14:47:19      ! From phylmd/clmain.F, version 1.6, 2005/11/16 14:47:19
16      ! Author: Z. X. Li (LMD/CNRS)      ! Author: Z. X. Li (LMD/CNRS)
# Line 35  contains Line 36  contains
36      USE interfoce_lim_m, ONLY: interfoce_lim      USE interfoce_lim_m, ONLY: interfoce_lim
37      use phyetat0_m, only: zmasq      use phyetat0_m, only: zmasq
38      use stdlevvar_m, only: stdlevvar      use stdlevvar_m, only: stdlevvar
39      USE suphec_m, ONLY: rd, rg      USE suphec_m, ONLY: rd, rg, rsigma
40      use time_phylmdz, only: itap      use time_phylmdz, only: itap
41    
42      REAL, INTENT(inout):: pctsrf(klon, nbsrf)      REAL, INTENT(inout):: pctsrf(klon, nbsrf)
# Line 68  contains Line 69  contains
69      REAL, intent(in):: snow_fall(klon)      REAL, intent(in):: snow_fall(klon)
70      ! solid water mass flux (kg / m2 / s), positive down      ! solid water mass flux (kg / m2 / s), positive down
71    
     REAL, INTENT(IN):: fsolsw(klon, nbsrf), fsollw(klon, nbsrf)  
72      REAL, intent(inout):: frugs(klon, nbsrf) ! longueur de rugosit\'e (en m)      REAL, intent(inout):: frugs(klon, nbsrf) ! longueur de rugosit\'e (en m)
73      real agesno(klon, nbsrf)      real agesno(klon, nbsrf)
74      REAL, INTENT(IN):: rugoro(klon)      REAL, INTENT(IN):: rugoro(klon)
# Line 126  contains Line 126  contains
126      real ffonte(klon, nbsrf) ! flux thermique utilise pour fondre la neige      real ffonte(klon, nbsrf) ! flux thermique utilise pour fondre la neige
127      REAL, intent(inout):: run_off_lic_0(:) ! (klon)      REAL, intent(inout):: run_off_lic_0(:) ! (klon)
128    
129        REAL, intent(out):: albsol(:) ! (klon)
130        ! albedo du sol total, visible, moyen par maille
131    
132        REAL, intent(in):: sollw(:) ! (klon)
133        ! rayonnement infrarouge montant \`a la surface
134        
135        REAL, intent(in):: solsw(:) ! (klon)
136        REAL, intent(in):: tsol(:) ! (klon)
137    
138      ! Local:      ! Local:
139    
140        REAL fsollw(klon, nbsrf) ! bilan flux IR pour chaque sous-surface
141        REAL fsolsw(klon, nbsrf) ! flux solaire absorb\'e pour chaque sous-surface
142    
143      ! la nouvelle repartition des surfaces sortie de l'interface      ! la nouvelle repartition des surfaces sortie de l'interface
144      REAL, save:: pctsrf_new_oce(klon)      REAL, save:: pctsrf_new_oce(klon)
145      REAL, save:: pctsrf_new_sic(klon)      REAL, save:: pctsrf_new_sic(klon)
# Line 186  contains Line 198  contains
198    
199      !------------------------------------------------------------      !------------------------------------------------------------
200    
201        albsol = sum(falbe * pctsrf, dim = 2)
202    
203        ! R\'epartition sous maille des flux longwave et shortwave
204        ! R\'epartition du longwave par sous-surface lin\'earis\'ee
205    
206        forall (nsrf = 1:nbsrf)
207           fsollw(:, nsrf) = sollw + 4. * RSIGMA * tsol**3 &
208                * (tsol - ftsol(:, nsrf))
209           fsolsw(:, nsrf) = solsw * (1. - falbe(:, nsrf)) / (1. - albsol)
210        END forall
211    
212      ytherm = 0.      ytherm = 0.
213    
214      DO k = 1, klev ! epaisseur de couche      DO k = 1, klev ! epaisseur de couche

Legend:
Removed from v.305  
changed lines
  Added in v.307

  ViewVC Help
Powered by ViewVC 1.1.21