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

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

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

revision 227 by guez, Thu Nov 2 15:47:03 2017 UTC revision 252 by guez, Mon Jan 22 15:02:56 2018 UTC
# Line 5  module HBTM_m Line 5  module HBTM_m
5  contains  contains
6    
7    SUBROUTINE HBTM(paprs, pplay, t2m, q2m, ustar, flux_t, flux_q, u, v, t, q, &    SUBROUTINE HBTM(paprs, pplay, t2m, q2m, ustar, flux_t, flux_q, u, v, t, q, &
8         pblh, cape, EauLiq, ctei, pblT, therm, trmb1, trmb2, trmb3, plcl)         pblh, cape, EauLiq, ctei, pblT, therm, plcl)
9    
10      ! D'apr\'es Holstag et Boville et Troen et Mahrt      ! D'apr\'es Holstag et Boville et Troen et Mahrt
11      ! JAS 47 BLM      ! JAS 47 BLM
# Line 63  contains Line 63  contains
63      REAL pblT(klon)      REAL pblT(klon)
64      ! thermal virtual temperature excess      ! thermal virtual temperature excess
65      REAL therm(klon)      REAL therm(klon)
     REAL trmb1(klon), trmb2(klon), trmb3(klon)  
66      REAL plcl(klon)      REAL plcl(klon)
67    
68      ! Local:      ! Local:
# Line 206  contains Line 205  contains
205         plcl(i) = 6000.         plcl(i) = 6000.
206         ! Lambda = -u*^3 / (alpha.g.kvon.<w'Theta'v>         ! Lambda = -u*^3 / (alpha.g.kvon.<w'Theta'v>
207         obklen(i) = -t(i, 1)*ustar(i)**3/(RG*vk*heatv(i))         obklen(i) = -t(i, 1)*ustar(i)**3/(RG*vk*heatv(i))
        trmb1(i) = 0.  
        trmb2(i) = 0.  
        trmb3(i) = 0.  
208      ENDDO      ENDDO
209    
210      ! PBL height calculation: Search for level of pbl. Scan upward      ! PBL height calculation: Search for level of pbl. Scan upward

Legend:
Removed from v.227  
changed lines
  Added in v.252

  ViewVC Help
Powered by ViewVC 1.1.21