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

Diff of /trunk/phylmd/phytrac.f

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

trunk/phylmd/phytrac.f revision 98 by guez, Tue May 13 17:23:16 2014 UTC trunk/Sources/phylmd/phytrac.f revision 156 by guez, Thu Jul 16 17:39:10 2015 UTC
# Line 8  module phytrac_m Line 8  module phytrac_m
8  contains  contains
9    
10    SUBROUTINE phytrac(itap, lmt_pas, julien, gmtime, firstcal, lafin, pdtphys, &    SUBROUTINE phytrac(itap, lmt_pas, julien, gmtime, firstcal, lafin, pdtphys, &
11         u, t_seri, paprs, pplay, pmfu, pmfd, pde_u, pen_d, coefh, fm_therm, &         t_seri, paprs, pplay, pmfu, pmfd, pde_u, pen_d, coefh, fm_therm, &
12         entr_therm, yu1, yv1, ftsol, pctsrf, frac_impa, frac_nucl, pphis, &         entr_therm, yu1, yv1, ftsol, pctsrf, frac_impa, frac_nucl, pphis, da, &
13         albsol, rh, cldfra, rneb, diafra, cldliq, pmflxr, pmflxs, prfl, psfl, &         phi, mp, upwd, dnwd, tr_seri, zmasse)
        da, phi, mp, upwd, dnwd, tr_seri, zmasse)  
14    
15      ! From phylmd/phytrac.F, version 1.15 2006/02/21 08:08:30 (SVN revision 679)      ! From phylmd/phytrac.F, version 1.15 2006/02/21 08:08:30 (SVN revision 679)
16    
# Line 30  contains Line 29  contains
29      use abort_gcm_m, only: abort_gcm      use abort_gcm_m, only: abort_gcm
30      use clesphys, only: ecrit_tra      use clesphys, only: ecrit_tra
31      use clesphys2, only: iflag_con      use clesphys2, only: iflag_con
32        use cltrac_m, only: cltrac
33      use cltracrn_m, only: cltracrn      use cltracrn_m, only: cltracrn
34      use ctherm, only: iflag_thermals      use ctherm, only: iflag_thermals
35        use cvltr_m, only: cvltr
36      use dimens_m, only: llm, nqmx      use dimens_m, only: llm, nqmx
37      use dimphy, only: klon      use dimphy, only: klon
38      use indicesol, only: nbsrf      use indicesol, only: nbsrf
# Line 54  contains Line 55  contains
55      logical, intent(in):: firstcal ! first call to "calfis"      logical, intent(in):: firstcal ! first call to "calfis"
56      logical, intent(in):: lafin ! fin de la physique      logical, intent(in):: lafin ! fin de la physique
57      real, intent(in):: pdtphys ! pas d'integration pour la physique (s)      real, intent(in):: pdtphys ! pas d'integration pour la physique (s)
     real, intent(in):: u(klon, llm)  
58      real, intent(in):: t_seri(klon, llm) ! temperature, in K      real, intent(in):: t_seri(klon, llm) ! temperature, in K
59    
60      real, intent(in):: paprs(klon, llm+1)      real, intent(in):: paprs(klon, llm+1)
# Line 82  contains Line 82  contains
82      REAL yv1(klon) ! vents au premier niveau      REAL yv1(klon) ! vents au premier niveau
83    
84      ! Arguments n\'ecessaires pour les sources et puits de traceur :      ! Arguments n\'ecessaires pour les sources et puits de traceur :
85      real ftsol(klon, nbsrf) ! Temperature du sol (surf)(Kelvin)      real, intent(in):: ftsol(klon, nbsrf) ! Temperature du sol (surf)(Kelvin)
86      real pctsrf(klon, nbsrf) ! Pourcentage de sol f(nature du sol)      real pctsrf(klon, nbsrf) ! Pourcentage de sol f(nature du sol)
87    
88      ! Lessivage pour le on-line      ! Lessivage pour le on-line
# Line 90  contains Line 90  contains
90      REAL frac_nucl(klon, llm) ! fraction d'aerosols nuclees      REAL frac_nucl(klon, llm) ! fraction d'aerosols nuclees
91    
92      real, intent(in):: pphis(klon)      real, intent(in):: pphis(klon)
     real albsol(klon) ! albedo surface  
     real rh(klon, llm) ! humidite relative  
     real cldfra(klon, llm) ! fraction nuageuse (tous les nuages)  
     real rneb(klon, llm) ! fraction nuageuse (grande echelle)  
   
     real diafra(klon, llm)  
     ! (fraction nuageuse (convection ou stratus artificiels))  
   
     real cldliq(klon, llm) ! eau liquide nuageuse  
     REAL pmflxr(klon, llm+1), pmflxs(klon, llm+1) !--lessivage convection  
     REAL prfl(klon, llm+1), psfl(klon, llm+1) !--lessivage large-scale  
93    
94      ! Kerry Emanuel      ! Kerry Emanuel
95      real da(klon, llm), phi(klon, llm, llm), mp(klon, llm)      real, intent(in):: da(klon, llm), phi(klon, llm, llm), mp(klon, llm)
96      REAL, intent(in):: upwd(klon, llm) ! saturated updraft mass flux      REAL, intent(in):: upwd(klon, llm) ! saturated updraft mass flux
97      REAL, intent(in):: dnwd(klon, llm) ! saturated downdraft mass flux      REAL, intent(in):: dnwd(klon, llm) ! saturated downdraft mass flux
98    
# Line 127  contains Line 116  contains
116      !      !
117      ! Pour la source de radon et son reservoir de sol      ! Pour la source de radon et son reservoir de sol
118    
119      REAL, save:: trs(klon, nqmx - 2) ! Concentration de radon dans le sol      REAL, save:: trs(klon, nqmx - 2) ! Concentration de traceur dans le sol
120    
121      REAL masktr(klon, nqmx - 2) ! Masque reservoir de sol traceur      REAL masktr(klon, nqmx - 2) ! Masque reservoir de sol traceur
122      ! Masque de l'echange avec la surface      ! Masque de l'echange avec la surface
# Line 166  contains Line 155  contains
155    
156      REAL d_tr(klon, llm), d_trs(klon) ! tendances de traceurs      REAL d_tr(klon, llm), d_trs(klon) ! tendances de traceurs
157      REAL d_tr_cl(klon, llm, nqmx - 2) ! tendance de traceurs couche limite      REAL d_tr_cl(klon, llm, nqmx - 2) ! tendance de traceurs couche limite
158      REAL d_tr_cv(klon, llm, nqmx - 2) ! tendance de traceurs conv pour chq traceur  
159        REAL d_tr_cv(klon, llm, nqmx - 2)
160        ! tendance de traceurs conv pour chq traceur
161    
162      REAL d_tr_th(klon, llm, nqmx - 2) ! la tendance des thermiques      REAL d_tr_th(klon, llm, nqmx - 2) ! la tendance des thermiques
163      REAL d_tr_dec(klon, llm, 2) ! la tendance de la decroissance      REAL d_tr_dec(klon, llm, 2) ! la tendance de la decroissance
164      ! ! radioactive du rn - > pb      ! ! radioactive du rn - > pb
# Line 247  contains Line 239  contains
239                    tr_seri(:, :, it), d_tr_cv(:, :, it))                    tr_seri(:, :, it), d_tr_cv(:, :, it))
240            else if (iflag_con == 3) then            else if (iflag_con == 3) then
241               ! Emanuel               ! Emanuel
242               call cvltr(pdtphys, da, phi, mp, paprs, tr_seri(1, 1, it), upwd, &               call cvltr(pdtphys, da, phi, mp, paprs, tr_seri(:, :, it), upwd, &
243                    dnwd, d_tr_cv(1, 1, it))                    dnwd, d_tr_cv(:, :, it))
244            endif            endif
245    
246            DO k = 1, llm            DO k = 1, llm
# Line 307  contains Line 299  contains
299         DO it=1, nqmx - 2         DO it=1, nqmx - 2
300            if (clsol(it)) then            if (clsol(it)) then
301               ! couche limite avec quantite dans le sol calculee               ! couche limite avec quantite dans le sol calculee
302               CALL cltracrn(it, pdtphys, yu1, yv1, &               CALL cltracrn(it, pdtphys, yu1, yv1, coefh, t_seri, ftsol, &
303                    coefh, t_seri, ftsol, pctsrf, &                    pctsrf, tr_seri(:, :, it), trs(:, it), paprs, pplay, delp, &
304                    tr_seri(:, :, it), trs(1, it), &                    masktr(1, it), fshtr(1, it), hsoltr(it), tautr(it), &
305                    paprs, pplay, delp, &                    vdeptr(it), rlat, d_tr_cl(1, 1, it), d_trs)
                   masktr(1, it), fshtr(1, it), hsoltr(it), &  
                   tautr(it), vdeptr(it), &  
                   rlat, &  
                   d_tr_cl(1, 1, it), d_trs)  
306               DO k = 1, llm               DO k = 1, llm
307                  DO i = 1, klon                  DO i = 1, klon
308                     tr_seri(i, k, it) = tr_seri(i, k, it) + d_tr_cl(i, k, it)                     tr_seri(i, k, it) = tr_seri(i, k, it) + d_tr_cl(i, k, it)
309                  ENDDO                  ENDDO
310               ENDDO               ENDDO
311    
312               ! Traceur ds sol               trs(:, it) = trs(:, it) + d_trs
313              else
314               DO i = 1, klon               ! couche limite avec flux prescrit
                 trs(i, it) = trs(i, it) + d_trs(i)  
              END DO  
           else ! couche limite avec flux prescrit  
315               !MAF provisoire source / traceur a creer               !MAF provisoire source / traceur a creer
316               DO i=1, klon               DO i=1, klon
317                  source(i) = 0.0 ! pas de source, pour l'instant                  source(i) = 0. ! pas de source, pour l'instant
318               ENDDO               ENDDO
319    
320               CALL cltrac(pdtphys, coefh, t_seri, &               CALL cltrac(pdtphys, coefh, t_seri, tr_seri(:, :, it), source, &
321                    tr_seri(1, 1, it), source, &                    paprs, pplay, delp, d_tr_cl(1, 1, it))
                   paprs, pplay, delp, &  
                   d_tr_cl(1, 1, it))  
322               DO k = 1, llm               DO k = 1, llm
323                  DO i = 1, klon                  DO i = 1, klon
324                     tr_seri(i, k, it) = tr_seri(i, k, it) + d_tr_cl(i, k, it)                     tr_seri(i, k, it) = tr_seri(i, k, it) + d_tr_cl(i, k, it)
# Line 439  contains Line 422  contains
422        use histsync_m, only: histsync        use histsync_m, only: histsync
423        use histwrite_m, only: histwrite        use histwrite_m, only: histwrite
424        use temps, only: itau_phy        use temps, only: itau_phy
425        use iniadvtrac_m, only: tnom        use iniadvtrac_m, only: tname
426        use comgeomphy, only: airephy        use comgeomphy, only: airephy
427        use dimphy, only: klon        use dimphy, only: klon
428        use grid_change, only: gr_phy_write_2d        use grid_change, only: gr_phy_write_2d
# Line 463  contains Line 446  contains
446        CALL histwrite(nid_tra, "zmasse", itau_w, gr_phy_write_3d(zmasse))        CALL histwrite(nid_tra, "zmasse", itau_w, gr_phy_write_3d(zmasse))
447    
448        DO it=1, nqmx - 2        DO it=1, nqmx - 2
449           CALL histwrite(nid_tra, tnom(it+2), itau_w, &           CALL histwrite(nid_tra, tname(it+2), itau_w, &
450                gr_phy_write_3d(tr_seri(:, :, it)))                gr_phy_write_3d(tr_seri(:, :, it)))
451           if (lessivage) THEN           if (lessivage) THEN
452              CALL histwrite(nid_tra, "fl"//tnom(it+2), itau_w, &              CALL histwrite(nid_tra, "fl"//tname(it+2), itau_w, &
453                   gr_phy_write_3d(flestottr(:, :, it)))                   gr_phy_write_3d(flestottr(:, :, it)))
454           endif           endif
455           CALL histwrite(nid_tra, "d_tr_th_"//tnom(it+2), itau_w, &           CALL histwrite(nid_tra, "d_tr_th_"//tname(it+2), itau_w, &
456                gr_phy_write_3d(d_tr_th(:, :, it)))                gr_phy_write_3d(d_tr_th(:, :, it)))
457           CALL histwrite(nid_tra, "d_tr_cv_"//tnom(it+2), itau_w, &           CALL histwrite(nid_tra, "d_tr_cv_"//tname(it+2), itau_w, &
458                gr_phy_write_3d(d_tr_cv(:, :, it)))                gr_phy_write_3d(d_tr_cv(:, :, it)))
459           CALL histwrite(nid_tra, "d_tr_cl_"//tnom(it+2), itau_w, &           CALL histwrite(nid_tra, "d_tr_cl_"//tname(it+2), itau_w, &
460                gr_phy_write_3d(d_tr_cl(:, :, it)))                gr_phy_write_3d(d_tr_cl(:, :, it)))
461        ENDDO        ENDDO
462    

Legend:
Removed from v.98  
changed lines
  Added in v.156

  ViewVC Help
Powered by ViewVC 1.1.21