/[lmdze]/trunk/phylmd/Interface_surf/calcul_fluxs.f90
ViewVC logotype

Diff of /trunk/phylmd/Interface_surf/calcul_fluxs.f90

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

revision 266 by guez, Thu Apr 19 17:54:55 2018 UTC revision 308 by guez, Tue Sep 18 15:14:40 2018 UTC
# Line 4  module calcul_fluxs_m Line 4  module calcul_fluxs_m
4    
5  contains  contains
6    
7    SUBROUTINE calcul_fluxs(dtime, tsurf, p1lay, cal, beta, coef1lay, ps, &    SUBROUTINE calcul_fluxs(tsurf, p1lay, cal, beta, cdragh, ps, qsurf, &
8         qsurf, radsol, dif_grnd, t1lay, q1lay, u1lay, v1lay, petAcoef, &         radsol, t1lay, q1lay, u1lay, v1lay, tAcoef, qAcoef, tBcoef, &
9         peqAcoef, petBcoef, peqBcoef, tsurf_new, evap, fluxlat, flux_t, &         qBcoef, tsurf_new, evap, fluxlat, flux_t, dflux_s, dflux_l, dif_grnd)
        dflux_s, dflux_l)  
10    
11      ! Cette routine calcule les flux en h et q à l'interface et une      ! Cette routine calcule les flux en h et q à l'interface et une
12      ! température de surface.      ! température de surface.
13    
14      ! L. Fairhead, April 2000      ! L. Fairhead, April 2000
15    
16      USE fcttre, ONLY: foede, foeew      ! Note that, if cal = 0, beta = 1 and dif_grnd = 0, then tsurf_new
17        ! = tsurf and qsurf = qsat.
18    
19        ! Libraries:
20      use nr_util, only: assert_eq      use nr_util, only: assert_eq
21    
22        use comconst, only: dtphys
23        USE fcttre, ONLY: foede, foeew
24      USE suphec_m, ONLY: rcpd, rd, retv, rlstt, rlvtt, rtt      USE suphec_m, ONLY: rcpd, rd, retv, rlstt, rlvtt, rtt
25      USE yoethf_m, ONLY: r2es, r5ies, r5les, rvtmp2      USE yoethf_m, ONLY: r2es, r5ies, r5les, rvtmp2
26    
     real, intent(IN):: dtime  
27      real, intent(IN):: tsurf(:) ! (knon) température de surface      real, intent(IN):: tsurf(:) ! (knon) température de surface
28    
29      real, intent(IN):: p1lay(:) ! (knon)      real, intent(IN):: p1lay(:) ! (knon)
# Line 27  contains Line 31  contains
31    
32      real, intent(IN):: cal(:) ! (knon) capacité calorifique du sol      real, intent(IN):: cal(:) ! (knon) capacité calorifique du sol
33      real, intent(IN):: beta(:) ! (knon) évaporation réelle      real, intent(IN):: beta(:) ! (knon) évaporation réelle
34      real, intent(IN):: coef1lay(:) ! (knon) coefficient d'échange      real, intent(IN):: cdragh(:) ! (knon) coefficient d'échange
35      real, intent(IN):: ps(:) ! (knon) pression au sol      real, intent(IN):: ps(:) ! (knon) pression au sol
36      real, intent(OUT):: qsurf(:) ! (knon) humidité de l'air au-dessus du sol      real, intent(OUT):: qsurf(:) ! (knon) humidité de l'air au-dessus du sol
37    
38      real, intent(IN):: radsol(:) ! (knon)      real, intent(IN):: radsol(:) ! (knon)
39      ! rayonnement net au sol (longwave + shortwave)      ! rayonnement net au sol (longwave + shortwave)
40    
41      real, intent(IN):: dif_grnd(:) ! (knon)      real, intent(IN):: dif_grnd ! coefficient de diffusion vers le sol profond
     ! coefficient de diffusion vers le sol profond  
   
42      real, intent(IN):: t1lay(:), q1lay(:), u1lay(:), v1lay(:) ! (knon)      real, intent(IN):: t1lay(:), q1lay(:), u1lay(:), v1lay(:) ! (knon)
43    
44      real, intent(IN):: petAcoef(:), peqAcoef(:) ! (knon)      real, intent(IN):: tAcoef(:), qAcoef(:) ! (knon)
45      ! coefficients A de la résolution de la couche limite pour T et q      ! coefficients A de la résolution de la couche limite pour T et q
46    
47      real, intent(IN):: petBcoef(:), peqBcoef(:) ! (knon)      real, intent(IN):: tBcoef(:), qBcoef(:) ! (knon)
48      ! coefficients B de la résolution de la couche limite pour t et q      ! coefficients B de la résolution de la couche limite pour t et q
49    
50      real, intent(OUT):: tsurf_new(:) ! (knon) température au sol      real, intent(OUT):: tsurf_new(:) ! (knon) température au sol
# Line 57  contains Line 59  contains
59    
60      ! Local:      ! Local:
61      integer i      integer i
62      integer knon ! nombre de points a traiter      integer knon ! nombre de points \`a traiter
63      real, dimension(size(ps)):: mh, oh, mq, nq, oq, dq_s_dt, coef ! (knon)      real, dimension(size(ps)):: mh, oh, mq, nq, oq, dq_s_dt, coef ! (knon)
64      real qsat(size(ps)) ! (knon) mass fraction      real qsat(size(ps)) ! (knon) mass fraction
65      real sl(size(ps)) ! (knon) chaleur latente d'évaporation ou de sublimation      real sl(size(ps)) ! (knon) chaleur latente d'évaporation ou de sublimation
66      logical delta      logical delta
67      real zcor      real zcor
68      real, parameter:: t_grnd = 271.35      real, parameter:: t_grnd = 271.35
69        real, parameter:: min_wind_speed = 1. ! in m s-1
70    
71      !---------------------------------------------------------------------      !---------------------------------------------------------------------
72    
73      knon = assert_eq((/size(tsurf), size(p1lay), size(cal), size(beta), &      knon = assert_eq([size(tsurf), size(p1lay), size(cal), size(beta), &
74           size(coef1lay), size(ps), size(qsurf), size(radsol), size(dif_grnd), &           size(cdragh), size(ps), size(qsurf), size(radsol), size(t1lay), &
75           size(t1lay), size(q1lay), size(u1lay), size(v1lay), size(petAcoef), &           size(q1lay), size(u1lay), size(v1lay), size(tAcoef), size(qAcoef), &
76           size(peqAcoef), size(petBcoef), size(peqBcoef), size(tsurf_new), &           size(tBcoef), size(qBcoef), size(tsurf_new), size(evap), &
77           size(evap), size(fluxlat), size(flux_t), size(dflux_s), &           size(fluxlat), size(flux_t), size(dflux_s), size(dflux_l)], &
78           size(dflux_l)/), "calcul_fluxs knon")           "calcul_fluxs knon")
79    
80      ! Traitement de l'humidité du sol      ! Traitement de l'humidité du sol
81    
# Line 86  contains Line 89  contains
89              qsat(i), zcor) / RLVTT              qsat(i), zcor) / RLVTT
90      ENDDO      ENDDO
91    
92      coef = coef1lay * (1. + SQRT(u1lay**2 + v1lay**2)) * p1lay / (RD * t1lay)      coef = cdragh * (min_wind_speed + SQRT(u1lay**2 + v1lay**2)) * p1lay &
93             / (RD * t1lay)
94      sl = merge(RLSTT, RLVTT, tsurf < RTT)      sl = merge(RLSTT, RLVTT, tsurf < RTT)
95    
96      ! Q      ! Q
97      oq = 1. - beta * coef * peqBcoef * dtime      oq = 1. - beta * coef * qBcoef * dtphys
98      mq = beta * coef * (peqAcoef - qsat + dq_s_dt * tsurf) / oq      mq = beta * coef * (qAcoef - qsat + dq_s_dt * tsurf) / oq
99      nq = beta * coef * (- 1. * dq_s_dt) / oq      nq = - beta * coef * dq_s_dt / oq
100    
101      ! H      ! H
102      oh = 1. - (coef * petBcoef * dtime)      oh = 1. - coef * tBcoef * dtphys
103      mh = coef * petAcoef / oh      mh = coef * tAcoef / oh
104      dflux_s = - (coef * RCPD)/ oh      dflux_s = - coef * RCPD / oh
105    
106      ! Tsurface      tsurf_new = (tsurf + cal / RCPD * dtphys * (radsol + mh + sl * mq) &
107      tsurf_new = (tsurf + cal / RCPD * dtime * (radsol + mh + sl * mq) &           + dif_grnd * t_grnd * dtphys) / (1. - dtphys * cal / RCPD * (dflux_s &
108           + dif_grnd * t_grnd * dtime) / (1. - dtime * cal / RCPD * (dflux_s &           + sl * nq) + dtphys * dif_grnd)
          + sl * nq) + dtime * dif_grnd)  
   
109      evap = - mq - nq * tsurf_new      evap = - mq - nq * tsurf_new
110      fluxlat = - evap * sl      fluxlat = - evap * sl
111      flux_t = mh + dflux_s * tsurf_new      flux_t = mh + dflux_s * tsurf_new
112      dflux_l = sl * nq      dflux_l = sl * nq
113        qsurf = (qAcoef - qBcoef * evap * dtphys) * (1. - beta) + beta * (qsat &
     ! Nouvelle valeur de l'humidité au dessus du sol :  
     qsurf = (peqAcoef - peqBcoef * evap * dtime) * (1. - beta) + beta * (qsat &  
114           + dq_s_dt * (tsurf_new - tsurf))           + dq_s_dt * (tsurf_new - tsurf))
115    
116    END SUBROUTINE calcul_fluxs    END SUBROUTINE calcul_fluxs

Legend:
Removed from v.266  
changed lines
  Added in v.308

  ViewVC Help
Powered by ViewVC 1.1.21