/[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 157 by guez, Mon Jul 20 16:01:49 2015 UTC revision 159 by guez, Tue Jul 21 15:29:52 2015 UTC
# Line 9  contains Line 9  contains
9    
10    SUBROUTINE phytrac(itap, lmt_pas, julien, gmtime, firstcal, lafin, pdtphys, &    SUBROUTINE phytrac(itap, lmt_pas, julien, gmtime, firstcal, lafin, pdtphys, &
11         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, da, &         entr_therm, yu1, yv1, ftsol, pctsrf, frac_impa, frac_nucl, da, phi, &
13         phi, mp, upwd, dnwd, tr_seri, zmasse, ncid_startphy)         mp, upwd, dnwd, tr_seri, zmasse, ncid_startphy, nid_ins)
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 36  contains Line 36  contains
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
     use ini_histrac_m, only: ini_histrac  
39      use initrrnpb_m, only: initrrnpb      use initrrnpb_m, only: initrrnpb
40      use minmaxqfi_m, only: minmaxqfi      use minmaxqfi_m, only: minmaxqfi
41      use netcdf95, only: nf95_inq_varid, nf95_get_var, nf95_put_var      use netcdf95, only: nf95_inq_varid, nf95_get_var, nf95_put_var
# Line 91  contains Line 90  contains
90      REAL frac_impa(klon, llm) ! fraction d'aerosols impactes      REAL frac_impa(klon, llm) ! fraction d'aerosols impactes
91      REAL frac_nucl(klon, llm) ! fraction d'aerosols nuclees      REAL frac_nucl(klon, llm) ! fraction d'aerosols nuclees
92    
     real, intent(in):: pphis(klon)  
   
93      ! Kerry Emanuel      ! Kerry Emanuel
94      real, intent(in):: da(klon, llm), phi(klon, llm, llm), mp(klon, llm)      real, intent(in):: da(klon, llm), phi(klon, llm, llm), mp(klon, llm)
95      REAL, intent(in):: upwd(klon, llm) ! saturated updraft mass flux      REAL, intent(in):: upwd(klon, llm) ! saturated updraft mass flux
# Line 104  contains Line 101  contains
101      real, intent(in):: zmasse(:, :) ! (klon, llm)      real, intent(in):: zmasse(:, :) ! (klon, llm)
102      ! (column-density of mass of air in a cell, in kg m-2)      ! (column-density of mass of air in a cell, in kg m-2)
103    
104      integer, intent(in):: ncid_startphy      integer, intent(in):: ncid_startphy, nid_ins
105    
106      ! Local:      ! Local:
107    
# Line 138  contains Line 135  contains
135      SAVE scavtr      SAVE scavtr
136    
137      CHARACTER itn      CHARACTER itn
     INTEGER, save:: nid_tra  
138    
139      ! nature du traceur      ! nature du traceur
140    
# Line 192  contains Line 188  contains
188         PRINT *, 'Frequency of tracer output: ecrit_tra = ', ecrit_tra         PRINT *, 'Frequency of tracer output: ecrit_tra = ', ecrit_tra
189         inirnpb = .true.         inirnpb = .true.
190    
        ! Initialisation des sorties :  
        call ini_histrac(nid_tra, pdtphys, nqmx - 2, lessivage)  
   
191         ! Initialisation de certaines variables pour le radon et le plomb         ! Initialisation de certaines variables pour le radon et le plomb
192         ! Initialisation du traceur dans le sol (couche limite radonique)         ! Initialisation du traceur dans le sol (couche limite radonique)
193         trs(:, 2:) = 0.         trs(:, 2:) = 0.
# Line 401  contains Line 394  contains
394      ENDIF      ENDIF
395    
396      ! Ecriture des sorties      ! Ecriture des sorties
397      call write_histrac(lessivage, itap, nid_tra)      call write_histrac(lessivage, itap, nid_ins)
398    
399      if (lafin) then      if (lafin) then
400         call nf95_inq_varid(ncid_restartphy, "trs", varid)         call nf95_inq_varid(ncid_restartphy, "trs", varid)
# Line 410  contains Line 403  contains
403    
404    contains    contains
405    
406      subroutine write_histrac(lessivage, itap, nid_tra)      subroutine write_histrac(lessivage, itap, nid_ins)
407    
408        ! 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
409    
# Line 419  contains Line 412  contains
412        use histwrite_m, only: histwrite        use histwrite_m, only: histwrite
413        use temps, only: itau_phy        use temps, only: itau_phy
414        use iniadvtrac_m, only: tname        use iniadvtrac_m, only: tname
       use comgeomphy, only: airephy  
415        use dimphy, only: klon        use dimphy, only: klon
416        use grid_change, only: gr_phy_write_2d        use grid_change, only: gr_phy_write_2d
417        use gr_phy_write_3d_m, only: gr_phy_write_3d        use gr_phy_write_3d_m, only: gr_phy_write_3d
418    
419        logical, intent(in):: lessivage        logical, intent(in):: lessivage
420        integer, intent(in):: itap ! number of calls to "physiq"        integer, intent(in):: itap ! number of calls to "physiq"
421        integer, intent(in):: nid_tra        integer, intent(in):: nid_ins
422    
423        ! Variables local to the procedure:        ! Variables local to the procedure:
424        integer it        integer it
425        integer itau_w ! pas de temps ecriture        integer itau_w ! pas de temps ecriture
       logical, parameter:: ok_sync = .true.  
426    
427        !-----------------------------------------------------        !-----------------------------------------------------
428    
429        itau_w = itau_phy + itap        itau_w = itau_phy + itap
430    
431        CALL histwrite(nid_tra, "phis", itau_w, gr_phy_write_2d(pphis))        CALL histwrite(nid_ins, "zmasse", itau_w, gr_phy_write_3d(zmasse))
       CALL histwrite(nid_tra, "aire", itau_w, gr_phy_write_2d(airephy))  
       CALL histwrite(nid_tra, "zmasse", itau_w, gr_phy_write_3d(zmasse))  
432    
433        DO it=1, nqmx - 2        DO it=1, nqmx - 2
434           CALL histwrite(nid_tra, tname(it+2), itau_w, &           CALL histwrite(nid_ins, tname(it+2), itau_w, &
435                gr_phy_write_3d(tr_seri(:, :, it)))                gr_phy_write_3d(tr_seri(:, :, it)))
436           if (lessivage) THEN           if (lessivage) THEN
437              CALL histwrite(nid_tra, "fl"//tname(it+2), itau_w, &              CALL histwrite(nid_ins, "fl"//tname(it+2), itau_w, &
438                   gr_phy_write_3d(flestottr(:, :, it)))                   gr_phy_write_3d(flestottr(:, :, it)))
439           endif           endif
440           CALL histwrite(nid_tra, "d_tr_th_"//tname(it+2), itau_w, &           CALL histwrite(nid_ins, "d_tr_th_"//tname(it+2), itau_w, &
441                gr_phy_write_3d(d_tr_th(:, :, it)))                gr_phy_write_3d(d_tr_th(:, :, it)))
442           CALL histwrite(nid_tra, "d_tr_cv_"//tname(it+2), itau_w, &           CALL histwrite(nid_ins, "d_tr_cv_"//tname(it+2), itau_w, &
443                gr_phy_write_3d(d_tr_cv(:, :, it)))                gr_phy_write_3d(d_tr_cv(:, :, it)))
444           CALL histwrite(nid_tra, "d_tr_cl_"//tname(it+2), itau_w, &           CALL histwrite(nid_ins, "d_tr_cl_"//tname(it+2), itau_w, &
445                gr_phy_write_3d(d_tr_cl(:, :, it)))                gr_phy_write_3d(d_tr_cl(:, :, it)))
446        ENDDO        ENDDO
447    
       CALL histwrite(nid_tra, "pplay", itau_w, gr_phy_write_3d(pplay))  
       CALL histwrite(nid_tra, "T", itau_w, gr_phy_write_3d(t_seri))  
   
       if (ok_sync) then  
          call histsync(nid_tra)  
       endif  
   
448      end subroutine write_histrac      end subroutine write_histrac
449    
450    END SUBROUTINE phytrac    END SUBROUTINE phytrac

Legend:
Removed from v.157  
changed lines
  Added in v.159

  ViewVC Help
Powered by ViewVC 1.1.21