/[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

trunk/libf/phylmd/hbtm.f90 revision 37 by guez, Tue Dec 21 15:45:48 2010 UTC trunk/phylmd/hbtm.f revision 103 by guez, Fri Aug 29 13:00:05 2014 UTC
# Line 8  contains Line 8  contains
8         flux_q, u, v, t, q, pblh, cape, EauLiq, ctei, pblT, therm, trmb1, &         flux_q, u, v, t, q, pblh, cape, EauLiq, ctei, pblT, therm, trmb1, &
9         trmb2, trmb3, plcl)         trmb2, trmb3, plcl)
10    
11      use dimens_m      ! D'après Holstag et Boville et Troen et Mahrt
     use dimphy  
     use YOMCST  
     use yoethf  
     use fcttre  
   
     ! D'apres Holstag & Boville et Troen & Mahrt  
12      ! JAS 47 BLM      ! JAS 47 BLM
13      ! Algorithme thèse Anne Mathieu      ! Algorithme thèse Anne Mathieu
14      ! Critère d'entraînement Peter Duynkerke (JAS 50)      ! Critère d'entraînement Peter Duynkerke (JAS 50)
# Line 35  contains Line 29  contains
29      ! mais on garde la possibilité de changer si besoin est (jusqu'à présent      ! mais on garde la possibilité de changer si besoin est (jusqu'à présent
30      ! la forme de HB avec le 1er niveau modele etait conservee)      ! la forme de HB avec le 1er niveau modele etait conservee)
31    
32        USE dimphy, ONLY: klev, klon
33        USE suphec_m, ONLY: rcpd, rd, retv, rg, rkappa, rlvtt, rtt, rv
34        USE yoethf_m, ONLY: r2es, rvtmp2
35        USE fcttre, ONLY: foeew
36    
37      REAL RLvCp, REPS      REAL RLvCp, REPS
38      ! Arguments:      ! Arguments:
39    
# Line 199  contains Line 198  contains
198      REAL zm(klon)      REAL zm(klon)
199      ! current level height + one level up      ! current level height + one level up
200      REAL zp(klon)      REAL zp(klon)
201      REAL zcor, zdelta, zcvm5      REAL zcor, zcvm5
202    
203      REAL fac, pblmin, zmzp, term      REAL fac, pblmin, zmzp, term
204    
# Line 447  contains Line 446  contains
446    
447      ! Main level loop to compute the diffusivities and      ! Main level loop to compute the diffusivities and
448      ! counter-gradient terms:      ! counter-gradient terms:
449      DO k = 2, isommet      loop_level: DO k = 2, isommet
450         ! Find levels within boundary layer:         ! Find levels within boundary layer:
451         DO i = 1, knon         DO i = 1, knon
452            unslev(i) = .FALSE.            unslev(i) = .FALSE.
# Line 517  contains Line 516  contains
516    
517         ! For all layers, compute integral info and CTEI         ! For all layers, compute integral info and CTEI
518         DO i = 1, knon         DO i = 1, knon
519            if (check(i).or.omegafl(i)) then            if (check(i) .or. omegafl(i)) then
520               if (.not.Zsat(i)) then               if (.not. Zsat(i)) then
521                  T2 = T2m(i) * s(i, k)                  T2 = T2m(i) * s(i, k)
522                  ! thermodyn functions                  ! thermodyn functions
523                  zdelta=MAX(0., SIGN(1., RTT - T2))                  qqsat= r2es * FOEEW(T2, RTT >= T2) / pplay(i, k)
                 qqsat= r2es * FOEEW(T2, zdelta) / pplay(i, k)  
524                  qqsat=MIN(0.5, qqsat)                  qqsat=MIN(0.5, qqsat)
525                  zcor=1./(1.-retv*qqsat)                  zcor=1./(1.-retv*qqsat)
526                  qqsat=qqsat*zcor                  qqsat=qqsat*zcor
# Line 543  contains Line 541  contains
541               ! cette ligne a deja ete faite normalement ?               ! cette ligne a deja ete faite normalement ?
542            endif            endif
543         ENDDO         ENDDO
544      end DO      end DO loop_level
545    
546    END SUBROUTINE HBTM    END SUBROUTINE HBTM
547    

Legend:
Removed from v.37  
changed lines
  Added in v.103

  ViewVC Help
Powered by ViewVC 1.1.21