/[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 18 by guez, Thu Aug 7 12:29:13 2008 UTC revision 32 by guez, Tue Apr 6 17:52:58 2010 UTC
# Line 12  contains Line 12  contains
12    SUBROUTINE phytrac(rnpb, itap, lmt_pas, julien, gmtime, firstcal, lafin, &    SUBROUTINE phytrac(rnpb, itap, lmt_pas, julien, gmtime, firstcal, lafin, &
13         nq_phys, pdtphys, u, v, t_seri, paprs, pplay, pmfu, pmfd, pen_u, &         nq_phys, 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, pphis, pphi, albsol, rh, cldfra, rneb, &
16         pphi, albsol, rh, cldfra, rneb, diafra, cldliq, itop_con, &         diafra, cldliq, itop_con, ibas_con, pmflxr, pmflxs, prfl, psfl, da, &
17         ibas_con, pmflxr, pmflxs, prfl, psfl, da, phi, mp, upwd, dnwd, &         phi, mp, upwd, dnwd, tr_seri, zmasse)
        tr_seri, zmasse)  
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
20    
# Line 91  contains Line 90  contains
90    
91      real pphi(klon, llm) ! geopotentiel      real pphi(klon, llm) ! geopotentiel
92      real pphis(klon)      real pphis(klon)
     REAL, intent(in):: presnivs(llm)  
93      logical, intent(in):: firstcal ! first call to "calfis"      logical, intent(in):: firstcal ! first call to "calfis"
94      logical, intent(in):: lafin ! fin de la physique      logical, intent(in):: lafin ! fin de la physique
95    
# Line 221  contains Line 219  contains
219         inirnpb=rnpb         inirnpb=rnpb
220    
221         ! Initialisation des sorties :         ! Initialisation des sorties :
222         call ini_histrac(nid_tra, pdtphys, presnivs, nq_phys, lessivage)         call ini_histrac(nid_tra, pdtphys, nq_phys, lessivage)
223    
224         ! Initialisation de certaines variables pour le radon et le plomb         ! Initialisation de certaines variables pour le radon et le plomb
225         ! Initialisation du traceur dans le sol (couche limite radonique)         ! Initialisation du traceur dans le sol (couche limite radonique)
# Line 470  contains Line 468  contains
468        ! 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
469    
470        use dimens_m, only: iim, jjm, llm        use dimens_m, only: iim, jjm, llm
471        use ioipsl, only: histwrite, histsync        use histcom, only: histsync
472          use histwrite_m, only: histwrite
473        use temps, only: itau_phy        use temps, only: itau_phy
474        use iniadvtrac_m, only: tnom        use iniadvtrac_m, only: tnom
475        use comgeomphy, only: airephy        use comgeomphy, only: airephy
476        use dimphy, only: klon        use dimphy, only: klon
477          use grid_change, only: gr_phy_write_2d
478          use gr_phy_write_3d_m, only: gr_phy_write_3d
479    
480        logical, intent(in):: lessivage        logical, intent(in):: lessivage
481    
# Line 487  contains Line 488  contains
488        ! Variables local to the procedure:        ! Variables local to the procedure:
489        integer it        integer it
490        integer itau_w   ! pas de temps ecriture        integer itau_w   ! pas de temps ecriture
       REAL zx_tmp_2d(iim, jjm+1), zx_tmp_3d(iim, jjm+1, llm)  
491        logical, parameter:: ok_sync = .true.        logical, parameter:: ok_sync = .true.
492    
493        !-----------------------------------------------------        !-----------------------------------------------------
494    
495        itau_w = itau_phy + itap        itau_w = itau_phy + itap
496    
497        CALL gr_fi_ecrit(1, klon, iim, jjm+1, pphis, zx_tmp_2d)        CALL histwrite(nid_tra, "phis", itau_w, gr_phy_write_2d(pphis))
498        CALL histwrite(nid_tra, "phis", itau_w, zx_tmp_2d)        CALL histwrite(nid_tra, "aire", itau_w, gr_phy_write_2d(airephy))
499          CALL histwrite(nid_tra, "zmasse", itau_w, gr_phy_write_3d(zmasse))
       CALL gr_fi_ecrit(1, klon, iim, jjm+1, airephy, zx_tmp_2d)        
       CALL histwrite(nid_tra, "aire", itau_w, zx_tmp_2d)  
   
       CALL gr_fi_ecrit(llm, klon, iim, jjm+1, zmasse, zx_tmp_3d)        
       CALL histwrite(nid_tra, "zmasse", itau_w, zx_tmp_3d)  
500    
501        DO it=1, nq_phys        DO it=1, nq_phys
502           CALL gr_fi_ecrit(llm, klon, iim, jjm+1, tr_seri(1, 1, it), zx_tmp_3d)           CALL histwrite(nid_tra, tnom(it+2), itau_w, &
503           CALL histwrite(nid_tra, tnom(it+2), itau_w, zx_tmp_3d)                gr_phy_write_3d(tr_seri(:, :, it)))
504           if (lessivage) THEN           if (lessivage) THEN
505              CALL gr_fi_ecrit(llm, klon, iim, jjm+1, flestottr(1, 1, it), &              CALL histwrite(nid_tra, "fl"//tnom(it+2), itau_w, &
506                   zx_tmp_3d)                   gr_phy_write_3d(flestottr(:, :, it)))
             CALL histwrite(nid_tra, "fl"//tnom(it+2), itau_w, zx_tmp_3d)  
507           endif           endif
508             CALL histwrite(nid_tra, "d_tr_th_"//tnom(it+2), itau_w, &
509           CALL gr_fi_ecrit(llm, klon, iim, jjm+1, d_tr_th(1, 1, it), zx_tmp_3d)                gr_phy_write_3d(d_tr_th(:, :, it)))
510           CALL histwrite(nid_tra, "d_tr_th_"//tnom(it+2), itau_w, zx_tmp_3d)           CALL histwrite(nid_tra, "d_tr_cv_"//tnom(it+2), itau_w, &
511           CALL gr_fi_ecrit(llm, klon, iim, jjm+1, d_tr_cv(1, 1, it), zx_tmp_3d)                gr_phy_write_3d(d_tr_cv(:, :, it)))
512           CALL histwrite(nid_tra, "d_tr_cv_"//tnom(it+2), itau_w, zx_tmp_3d)           CALL histwrite(nid_tra, "d_tr_cl_"//tnom(it+2), itau_w, &
513           CALL gr_fi_ecrit(llm, klon, iim, jjm+1, d_tr_cl(1, 1, it), zx_tmp_3d)                gr_phy_write_3d(d_tr_cl(:, :, it)))
          CALL histwrite(nid_tra, "d_tr_cl_"//tnom(it+2), itau_w, zx_tmp_3d)  
514        ENDDO        ENDDO
515    
516        CALL gr_fi_ecrit(llm, klon, iim, jjm+1, pplay, zx_tmp_3d)        CALL histwrite(nid_tra, "pplay", itau_w, gr_phy_write_3d(pplay))
517        CALL histwrite(nid_tra, "pplay", itau_w, zx_tmp_3d)        CALL histwrite(nid_tra, "T", itau_w, gr_phy_write_3d(t_seri))
   
       CALL gr_fi_ecrit(llm, klon, iim, jjm+1, t_seri, zx_tmp_3d)  
       CALL histwrite(nid_tra, "t", itau_w, zx_tmp_3d)  
518    
519        if (ok_sync) then        if (ok_sync) then
520           call histsync(nid_tra)           call histsync(nid_tra)

Legend:
Removed from v.18  
changed lines
  Added in v.32

  ViewVC Help
Powered by ViewVC 1.1.21