/[lmdze]/trunk/libf/phylmd/phytrac.f90
ViewVC logotype

Diff of /trunk/libf/phylmd/phytrac.f90

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

revision 7 by guez, Mon Mar 31 12:24:17 2008 UTC revision 12 by guez, Mon Jul 21 16:05:07 2008 UTC
# Line 13  contains Line 13  contains
13         nqmax, pdtphys, u, v, t_seri, paprs, pplay, pmfu, pmfd, pen_u, &         nqmax, pdtphys, u, v, t_seri, paprs, pplay, pmfu, pmfd, pen_u, &
14         pde_u, pen_d, pde_d, coefh, fm_therm, entr_therm, yu1, yv1, ftsol, &         pde_u, pen_d, pde_d, coefh, fm_therm, entr_therm, yu1, yv1, ftsol, &
15         pctsrf, frac_impa, frac_nucl, presnivs, pphis, &         pctsrf, frac_impa, frac_nucl, presnivs, pphis, &
16         pphi, albsol, sh, rh, cldfra, rneb, diafra, cldliq, itop_con, &         pphi, albsol, rh, cldfra, rneb, diafra, cldliq, itop_con, &
17         ibas_con, pmflxr, pmflxs, prfl, psfl, da, phi, mp, upwd, dnwd, tr_seri)         ibas_con, pmflxr, pmflxs, prfl, psfl, da, phi, mp, upwd, dnwd, tr_seri)
18    
19      ! From phylmd/phytrac.F, version 1.15 2006/02/21 08:08:30      ! From phylmd/phytrac.F, version 1.15 2006/02/21 08:08:30
# Line 33  contains Line 33  contains
33      use dimens_m, only: iim, jjm, llm      use dimens_m, only: iim, jjm, llm
34      use indicesol, only: nbsrf      use indicesol, only: nbsrf
35      use dimphy, only: klon, nbtr      use dimphy, only: klon, nbtr
36      use clesphys, only: ecrit_tra, iflag_con      use clesphys, only: ecrit_tra
37        use clesphys2, only: iflag_con
38      use abort_gcm_m, only: abort_gcm      use abort_gcm_m, only: abort_gcm
39      use YOMCST, only: rg      use YOMCST, only: rg
40      use ctherm, only: iflag_thermals      use ctherm, only: iflag_thermals
# Line 66  contains Line 67  contains
67    
68      real u(klon, llm)      real u(klon, llm)
69      real v(klon, llm)      real v(klon, llm)
     real sh(klon, llm)     ! humidite specifique  
70      real rh(klon, llm)     ! humidite relative      real rh(klon, llm)     ! humidite relative
71      real cldliq(klon, llm) ! eau liquide nuageuse      real cldliq(klon, llm) ! eau liquide nuageuse
72      real cldfra(klon, llm) ! fraction nuageuse (tous les nuages)      real cldfra(klon, llm) ! fraction nuageuse (tous les nuages)
# Line 80  contains Line 80  contains
80      real, intent(in):: paprs(klon, llm+1)      real, intent(in):: paprs(klon, llm+1)
81      ! (pression pour chaque inter-couche, en Pa)      ! (pression pour chaque inter-couche, en Pa)
82    
83      real pplay(klon, llm)  ! pression pour le mileu de chaque couche (en Pa)      real, intent(in):: pplay(klon, llm)
84        ! (pression pour le mileu de chaque couche, en Pa)
85    
86      real pphi(klon, llm) ! geopotentiel      real pphi(klon, llm) ! geopotentiel
87      real pphis(klon)      real pphis(klon)
88      REAL, intent(in):: presnivs(llm)      REAL, intent(in):: presnivs(llm)
# Line 279  contains Line 281  contains
281            if (iflag_con.eq.2) then            if (iflag_con.eq.2) then
282               ! tiedke               ! tiedke
283               CALL nflxtr(pdtphys, pmfu, pmfd, pen_u, pde_u, pen_d, pde_d, &               CALL nflxtr(pdtphys, pmfu, pmfd, pen_u, pde_u, pen_d, pde_d, &
284                    pplay, paprs, tr_seri(1, 1, it), d_tr_cv(1, 1, it))                    paprs, tr_seri(1, 1, it), d_tr_cv(1, 1, it))
285            else if (iflag_con.eq.3) then            else if (iflag_con.eq.3) then
286               ! KE               ! KE
287               call cvltr(pdtphys, da, phi, mp, paprs, pplay, &               call cvltr(pdtphys, da, phi, mp, paprs, &
288                    tr_seri(1, 1, it), upwd, dnwd, d_tr_cv(1, 1, it))                    tr_seri(1, 1, it), upwd, dnwd, d_tr_cv(1, 1, it))
289            endif            endif
290    

Legend:
Removed from v.7  
changed lines
  Added in v.12

  ViewVC Help
Powered by ViewVC 1.1.21