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

Diff of /trunk/phylmd/phytrac.f

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

revision 181 by guez, Tue Mar 15 17:51:30 2016 UTC revision 203 by guez, Wed Jun 8 15:10:12 2016 UTC
# Line 7  module phytrac_m Line 7  module phytrac_m
7    
8  contains  contains
9    
10    SUBROUTINE phytrac(itap, lmt_pas, julien, gmtime, firstcal, lafin, pdtphys, &    SUBROUTINE phytrac(julien, gmtime, firstcal, lafin, pdtphys, t_seri, paprs, &
11         t_seri, paprs, pplay, pmfu, pmfd, pde_u, pen_d, coefh, fm_therm, &         pplay, pmfu, pmfd, pde_u, pen_d, coefh, fm_therm, entr_therm, yu1, &
12         entr_therm, yu1, yv1, ftsol, pctsrf, frac_impa, frac_nucl, da, phi, &         yv1, ftsol, pctsrf, frac_impa, frac_nucl, da, phi, mp, upwd, dnwd, &
13         mp, upwd, dnwd, tr_seri, zmasse, ncid_startphy, nid_ins, itau_phy)         tr_seri, zmasse, ncid_startphy)
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
16        ! revision 679) and phylmd/write_histrac.h, version 1.9 2006/02/21
17        ! 08:08:30
18    
19      ! Authors: Fr\'ed\'eric Hourdin, Abderrahmane Idelkadi, Marie-Alice      ! Authors: Fr\'ed\'eric Hourdin, Abderrahmane Idelkadi, Marie-Alice
20      ! Foujols, Olivia      ! Foujols, Olivia
# Line 27  contains Line 29  contains
29      ! - stockage des moyennes des champs n\'ecessaires en mode traceur off-line      ! - stockage des moyennes des champs n\'ecessaires en mode traceur off-line
30    
31      use abort_gcm_m, only: abort_gcm      use abort_gcm_m, only: abort_gcm
32      use clesphys, only: ecrit_tra      use clesphys2, only: conv_emanuel
     use clesphys2, only: iflag_con  
33      use cltrac_m, only: cltrac      use cltrac_m, only: cltrac
34      use cltracrn_m, only: cltracrn      use cltracrn_m, only: cltracrn
35        USE conf_gcm_m, ONLY: lmt_pas
36      use ctherm, only: iflag_thermals      use ctherm, only: iflag_thermals
37      use cvltr_m, only: cvltr      use cvltr_m, only: cvltr
38      use dimens_m, only: llm, nqmx      use dimens_m, only: llm, nqmx
39      use dimphy, only: klon      use dimphy, only: klon
40        use histwrite_phy_m, only: histwrite_phy
41      use indicesol, only: nbsrf      use indicesol, only: nbsrf
42        use iniadvtrac_m, only: tname
43      use initrrnpb_m, only: initrrnpb      use initrrnpb_m, only: initrrnpb
44      use minmaxqfi_m, only: minmaxqfi      use minmaxqfi_m, only: minmaxqfi
45      use netcdf, only: NF90_FILL_float      use netcdf, only: NF90_FILL_float
# Line 49  contains Line 53  contains
53      use radiornpb_m, only: radiornpb      use radiornpb_m, only: radiornpb
54      use regr_pr_comb_coefoz_m, only: regr_pr_comb_coefoz      use regr_pr_comb_coefoz_m, only: regr_pr_comb_coefoz
55      use SUPHEC_M, only: rg      use SUPHEC_M, only: rg
56        use time_phylmdz, only: itap
57    
     integer, intent(in):: itap ! number of calls to "physiq"  
     integer, intent(in):: lmt_pas ! number of time steps of "physics" per day  
58      integer, intent(in):: julien !jour julien, 1 <= julien <= 360      integer, intent(in):: julien !jour julien, 1 <= julien <= 360
59      real, intent(in):: gmtime ! heure de la journ\'ee en fraction de jour      real, intent(in):: gmtime ! heure de la journ\'ee en fraction de jour
60      logical, intent(in):: firstcal ! first call to "calfis"      logical, intent(in):: firstcal ! first call to "calfis"
# Line 85  contains Line 88  contains
88    
89      ! Arguments n\'ecessaires pour les sources et puits de traceur :      ! Arguments n\'ecessaires pour les sources et puits de traceur :
90      real, intent(in):: ftsol(klon, nbsrf) ! Temperature du sol (surf)(Kelvin)      real, intent(in):: ftsol(klon, nbsrf) ! Temperature du sol (surf)(Kelvin)
91      real pctsrf(klon, nbsrf) ! Pourcentage de sol f(nature du sol)      real, intent(in):: pctsrf(klon, nbsrf) ! Pourcentage de sol f(nature du sol)
92    
93      ! Lessivage pour le on-line      ! Lessivage pour le on-line
94      REAL frac_impa(klon, llm) ! fraction d'aerosols impactes      REAL frac_impa(klon, llm) ! fraction d'aerosols impactes
# Line 102  contains Line 105  contains
105      real, intent(in):: zmasse(:, :) ! (klon, llm)      real, intent(in):: zmasse(:, :) ! (klon, llm)
106      ! (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)
107    
108      integer, intent(in):: ncid_startphy, nid_ins, itau_phy      integer, intent(in):: ncid_startphy
109    
110      ! Local:      ! Local:
111    
# Line 186  contains Line 189  contains
189    
190      if (firstcal) then      if (firstcal) then
191         print *, 'phytrac: pdtphys = ', pdtphys         print *, 'phytrac: pdtphys = ', pdtphys
        PRINT *, 'Frequency of tracer output: ecrit_tra = ', ecrit_tra  
192         inirnpb = .true.         inirnpb = .true.
193    
194         ! Initialisation de certaines variables pour le radon et le plomb         ! Initialisation de certaines variables pour le radon et le plomb
# Line 230  contains Line 232  contains
232      if (convection) then      if (convection) then
233         ! Calcul de l'effet de la convection         ! Calcul de l'effet de la convection
234         DO it=1, nqmx - 2         DO it=1, nqmx - 2
235            if (iflag_con == 2) then            if (conv_emanuel) then
              ! Tiedke  
              CALL nflxtr(pdtphys, pmfu, pmfd, pde_u, pen_d, paprs, &  
                   tr_seri(:, :, it), d_tr_cv(:, :, it))  
           else  
              ! iflag_con >= 3  
              ! Emanuel  
236               call cvltr(pdtphys, da, phi, mp, paprs, tr_seri(:, :, it), upwd, &               call cvltr(pdtphys, da, phi, mp, paprs, tr_seri(:, :, it), upwd, &
237                    dnwd, d_tr_cv(:, :, it))                    dnwd, d_tr_cv(:, :, it))
238              else
239                 CALL nflxtr(pdtphys, pmfu, pmfd, pde_u, pen_d, paprs, &
240                      tr_seri(:, :, it), d_tr_cv(:, :, it))
241            endif            endif
242    
243            DO k = 1, llm            DO k = 1, llm
# Line 398  contains Line 397  contains
397      ENDIF      ENDIF
398    
399      ! Ecriture des sorties      ! Ecriture des sorties
400      call write_histrac(lessivage, itap, nid_ins)      CALL histwrite_phy("zmasse", zmasse)
401        DO it=1, nqmx - 2
402           CALL histwrite_phy(tname(it+2), tr_seri(:, :, it))
403           if (lessivage) THEN
404              CALL histwrite_phy("fl"//tname(it+2), flestottr(:, :, it))
405           endif
406           CALL histwrite_phy("d_tr_th_"//tname(it+2), d_tr_th(:, :, it))
407           CALL histwrite_phy("d_tr_cv_"//tname(it+2), d_tr_cv(:, :, it))
408           CALL histwrite_phy("d_tr_cl_"//tname(it+2), d_tr_cl(:, :, it))
409        ENDDO
410    
411      if (lafin) then      if (lafin) then
412         call nf95_inq_varid(ncid_restartphy, "trs", varid)         call nf95_inq_varid(ncid_restartphy, "trs", varid)
413         call nf95_put_var(ncid_restartphy, varid, trs(:, 1))         call nf95_put_var(ncid_restartphy, varid, trs(:, 1))
414      endif      endif
415    
   contains  
   
     subroutine write_histrac(lessivage, itap, nid_ins)  
   
       ! From phylmd/write_histrac.h, version 1.9 2006/02/21 08:08:30  
   
       use histwrite_m, only: histwrite  
       use iniadvtrac_m, only: tname  
       use gr_phy_write_3d_m, only: gr_phy_write_3d  
   
       logical, intent(in):: lessivage  
       integer, intent(in):: itap ! number of calls to "physiq"  
       integer, intent(in):: nid_ins  
   
       ! Variables local to the procedure:  
       integer it  
       integer itau_w ! pas de temps ecriture  
   
       !-----------------------------------------------------  
   
       itau_w = itau_phy + itap  
   
       CALL histwrite(nid_ins, "zmasse", itau_w, gr_phy_write_3d(zmasse))  
   
       DO it=1, nqmx - 2  
          CALL histwrite(nid_ins, tname(it+2), itau_w, &  
               gr_phy_write_3d(tr_seri(:, :, it)))  
          if (lessivage) THEN  
             CALL histwrite(nid_ins, "fl"//tname(it+2), itau_w, &  
                  gr_phy_write_3d(flestottr(:, :, it)))  
          endif  
          CALL histwrite(nid_ins, "d_tr_th_"//tname(it+2), itau_w, &  
               gr_phy_write_3d(d_tr_th(:, :, it)))  
          CALL histwrite(nid_ins, "d_tr_cv_"//tname(it+2), itau_w, &  
               gr_phy_write_3d(d_tr_cv(:, :, it)))  
          CALL histwrite(nid_ins, "d_tr_cl_"//tname(it+2), itau_w, &  
               gr_phy_write_3d(d_tr_cl(:, :, it)))  
       ENDDO  
   
     end subroutine write_histrac  
   
416    END SUBROUTINE phytrac    END SUBROUTINE phytrac
417    
418  end module phytrac_m  end module phytrac_m

Legend:
Removed from v.181  
changed lines
  Added in v.203

  ViewVC Help
Powered by ViewVC 1.1.21