/[lmdze]/trunk/Sources/phylmd/phytrac.f
ViewVC logotype

Diff of /trunk/Sources/phylmd/phytrac.f

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

revision 34 by guez, Wed Jun 2 11:01:12 2010 UTC revision 72 by guez, Tue Jul 23 13:00:07 2013 UTC
# Line 8  module phytrac_m Line 8  module phytrac_m
8  contains  contains
9    
10    SUBROUTINE phytrac(rnpb, itap, lmt_pas, julien, gmtime, firstcal, lafin, &    SUBROUTINE phytrac(rnpb, itap, lmt_pas, julien, gmtime, firstcal, lafin, &
11         nq_phys, pdtphys, u, v, t_seri, paprs, pplay, pmfu, pmfd, pen_u, &         nq_phys, pdtphys, u, t_seri, paprs, pplay, pmfu, pmfd, pen_u, pde_u, &
12         pde_u, pen_d, pde_d, coefh, fm_therm, entr_therm, yu1, yv1, ftsol, &         pen_d, pde_d, coefh, fm_therm, entr_therm, yu1, yv1, ftsol, pctsrf, &
13         pctsrf, frac_impa, frac_nucl, pphis, pphi, albsol, rh, cldfra, rneb, &         frac_impa, frac_nucl, pphis, albsol, rh, cldfra, rneb, diafra, cldliq, &
14         diafra, cldliq, pmflxr, pmflxs, prfl, psfl, da, &         pmflxr, pmflxs, prfl, psfl, da, phi, mp, upwd, dnwd, tr_seri, zmasse)
        phi, mp, upwd, dnwd, tr_seri, zmasse)  
15    
16      ! 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 (SVN revision 679)
17    
18      ! Authors: Frédéric Hourdin, Abderrahmane Idelkadi, Marie-Alice      ! Authors: Frédéric Hourdin, Abderrahmane Idelkadi, Marie-Alice
19      ! Foujols, Olivia      ! Foujols, Olivia
# Line 24  contains Line 23  contains
23      ! les vrais traceurs (en nombre "nbtr", sans la vapeur d'eau ni l'eau      ! les vrais traceurs (en nombre "nbtr", sans la vapeur d'eau ni l'eau
24      ! liquide) dans "phytrac".      ! liquide) dans "phytrac".
25    
26        ! Modifications pour les traceurs :
27        ! - uniformisation des parametrisations dans phytrac
28        ! - stockage des moyennes des champs nécessaires en mode traceur off-line
29    
30      use dimens_m, only: llm      use dimens_m, only: llm
31      use indicesol, only: nbsrf      use indicesol, only: nbsrf
32      use dimphy, only: klon, nbtr      use dimphy, only: klon, nbtr
33      use clesphys, only: ecrit_tra      use clesphys, only: ecrit_tra
34      use clesphys2, only: iflag_con      use clesphys2, only: iflag_con
35      use abort_gcm_m, only: abort_gcm      use abort_gcm_m, only: abort_gcm
36      use YOMCST, only: rg      use SUPHEC_M, only: rg
37      use ctherm, only: iflag_thermals      use ctherm, only: iflag_thermals
38      use regr_pr_comb_coefoz_m, only: regr_pr_comb_coefoz      use regr_pr_comb_coefoz_m, only: regr_pr_comb_coefoz
39      use phyetat0_m, only: rlat      use phyetat0_m, only: rlat
# Line 38  contains Line 41  contains
41      use ini_histrac_m, only: ini_histrac      use ini_histrac_m, only: ini_histrac
42      use radiornpb_m, only: radiornpb      use radiornpb_m, only: radiornpb
43      use minmaxqfi_m, only: minmaxqfi      use minmaxqfi_m, only: minmaxqfi
44      use numer_rec, only: assert      use nr_util, only: assert
45      use press_coefoz_m, only: press_coefoz      use press_coefoz_m, only: press_coefoz
46    
47      logical, intent(in):: rnpb      logical, intent(in):: rnpb
# Line 56  contains Line 59  contains
59      real, intent(inout):: tr_seri(:, :, :) ! (klon, llm, nbtr)      real, intent(inout):: tr_seri(:, :, :) ! (klon, llm, nbtr)
60      ! (mass fractions of tracers, excluding water, at mid-layers)      ! (mass fractions of tracers, excluding water, at mid-layers)
61    
62      real u(klon, llm)      real, intent(in):: u(klon, llm)
     real v(klon, llm)  
63      real rh(klon, llm)     ! humidite relative      real rh(klon, llm)     ! humidite relative
64      real cldliq(klon, llm) ! eau liquide nuageuse      real cldliq(klon, llm) ! eau liquide nuageuse
65      real cldfra(klon, llm) ! fraction nuageuse (tous les nuages)      real cldfra(klon, llm) ! fraction nuageuse (tous les nuages)
# Line 74  contains Line 76  contains
76      real, intent(in):: pplay(klon, llm)      real, intent(in):: pplay(klon, llm)
77      ! (pression pour le mileu de chaque couche, en Pa)      ! (pression pour le mileu de chaque couche, en Pa)
78    
79      real pphi(klon, llm) ! geopotentiel      real, intent(in):: pphis(klon)
     real pphis(klon)  
80      logical, intent(in):: firstcal ! first call to "calfis"      logical, intent(in):: firstcal ! first call to "calfis"
81      logical, intent(in):: lafin ! fin de la physique      logical, intent(in):: lafin ! fin de la physique
82    
# Line 83  contains Line 84  contains
84      REAL prfl(klon, llm+1),   psfl(klon, llm+1)     !--lessivage large-scale      REAL prfl(klon, llm+1),   psfl(klon, llm+1)     !--lessivage large-scale
85    
86      !   convection:      !   convection:
87      REAL pmfu(klon, llm)  ! flux de masse dans le panache montant  
88      REAL pmfd(klon, llm)  ! flux de masse dans le panache descendant      REAL, intent(in):: pmfu(klon, llm) ! flux de masse dans le panache montant
89    
90        REAL, intent(in):: pmfd(klon, llm)
91        ! flux de masse dans le panache descendant
92    
93      REAL pen_u(klon, llm) ! flux entraine dans le panache montant      REAL pen_u(klon, llm) ! flux entraine dans le panache montant
94    
95      !   thermiques:      !   thermiques:
# Line 94  contains Line 99  contains
99      REAL pde_u(klon, llm) ! flux detraine dans le panache montant      REAL pde_u(klon, llm) ! flux detraine dans le panache montant
100      REAL pen_d(klon, llm) ! flux entraine dans le panache descendant      REAL pen_d(klon, llm) ! flux entraine dans le panache descendant
101      REAL pde_d(klon, llm) ! flux detraine dans le panache descendant      REAL pde_d(klon, llm) ! flux detraine dans le panache descendant
102      ! KE      ! Kerry Emanuel
103      real da(klon, llm), phi(klon, llm, llm), mp(klon, llm)      real da(klon, llm), phi(klon, llm, llm), mp(klon, llm)
104      REAL upwd(klon, llm)      ! saturated updraft mass flux      REAL, intent(in):: upwd(klon, llm) ! saturated updraft mass flux
105      REAL dnwd(klon, llm)      ! saturated downdraft mass flux      REAL, intent(in):: dnwd(klon, llm) ! saturated downdraft mass flux
106    
107      !   Couche limite:      !   Couche limite:
108    
# Line 235  contains Line 240  contains
240         end if         end if
241      ENDIF      ENDIF
242    
     ! Initialisation du traceur dans le sol (couche limite radonique)  
243      if (inirnpb) THEN      if (inirnpb) THEN
244           ! Initialisation du traceur dans le sol (couche limite radonique)
245         radio(1)= .true.         radio(1)= .true.
246         radio(2)= .true.         radio(2)= .true.
247         clsol(1)= .true.         clsol(1)= .true.
248         clsol(2)= .true.         clsol(2)= .true.
249         aerosol(2) = .TRUE. ! le Pb est un aerosol         aerosol(2) = .TRUE. ! le Pb est un aerosol
   
250         call initrrnpb(ftsol, pctsrf, masktr, fshtr, hsoltr, tautr, vdeptr, &         call initrrnpb(ftsol, pctsrf, masktr, fshtr, hsoltr, tautr, vdeptr, &
251              scavtr)              scavtr)
252         inirnpb=.false.         inirnpb=.false.
253      endif      endif
254    
     ! Calcul de l'effet de la convection  
   
255      if (convection) then      if (convection) then
256           ! Calcul de l'effet de la convection
257         DO it=1, nq_phys         DO it=1, nq_phys
258            if (iflag_con.eq.2) then            if (iflag_con == 2) then
259               ! tiedke               ! Tiedke
260               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, &
261                    paprs, tr_seri(1, 1, it), d_tr_cv(1, 1, it))                    paprs, tr_seri(1, 1, it), d_tr_cv(1, 1, it))
262            else if (iflag_con.eq.3) then            else if (iflag_con == 3) then
263               ! KE               ! Emanuel
264               call cvltr(pdtphys, da, phi, mp, paprs, &               call cvltr(pdtphys, da, phi, mp, paprs, tr_seri(1, 1, it), upwd, &
265                    tr_seri(1, 1, it), upwd, dnwd, d_tr_cv(1, 1, it))                    dnwd, d_tr_cv(1, 1, it))
266            endif            endif
267    
268            DO k = 1, llm            DO k = 1, llm
# Line 454  contains Line 456  contains
456        ! From phylmd/write_histrac.h, version 1.9 2006/02/21 08:08:30        ! From phylmd/write_histrac.h, version 1.9 2006/02/21 08:08:30
457    
458        use dimens_m, only: iim, jjm, llm        use dimens_m, only: iim, jjm, llm
459        use histcom, only: histsync        use histsync_m, only: histsync
460        use histwrite_m, only: histwrite        use histwrite_m, only: histwrite
461        use temps, only: itau_phy        use temps, only: itau_phy
462        use iniadvtrac_m, only: tnom        use iniadvtrac_m, only: tnom

Legend:
Removed from v.34  
changed lines
  Added in v.72

  ViewVC Help
Powered by ViewVC 1.1.21