/[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 156 by guez, Thu Jul 16 17:39:10 2015 UTC revision 157 by guez, Mon Jul 20 16:01:49 2015 UTC
# Line 10  contains Line 10  contains
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, pphis, da, &
13         phi, mp, upwd, dnwd, tr_seri, zmasse)         phi, mp, upwd, dnwd, 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 revision 679)
16    
# Line 39  contains Line 39  contains
39      use ini_histrac_m, only: ini_histrac      use ini_histrac_m, only: ini_histrac
40      use initrrnpb_m, only: initrrnpb      use initrrnpb_m, only: initrrnpb
41      use minmaxqfi_m, only: minmaxqfi      use minmaxqfi_m, only: minmaxqfi
42        use netcdf95, only: nf95_inq_varid, nf95_get_var, nf95_put_var
43      use nflxtr_m, only: nflxtr      use nflxtr_m, only: nflxtr
44      use nr_util, only: assert      use nr_util, only: assert
45      use o3_chem_m, only: o3_chem      use o3_chem_m, only: o3_chem
46      use phyetat0_m, only: rlat      use phyetat0_m, only: rlat
47        use phyredem0_m, only: ncid_restartphy
48      use press_coefoz_m, only: press_coefoz      use press_coefoz_m, only: press_coefoz
49      use radiornpb_m, only: radiornpb      use radiornpb_m, only: radiornpb
50      use regr_pr_comb_coefoz_m, only: regr_pr_comb_coefoz      use regr_pr_comb_coefoz_m, only: regr_pr_comb_coefoz
# Line 102  contains Line 104  contains
104      real, intent(in):: zmasse(:, :) ! (klon, llm)      real, intent(in):: zmasse(:, :) ! (klon, llm)
105      ! (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)
106    
107      ! Variables local to the procedure:      integer, intent(in):: ncid_startphy
108    
109        ! Local:
110    
111      integer nsplit      integer nsplit
112    
# Line 170  contains Line 174  contains
174      ! ! dans chaque couche      ! ! dans chaque couche
175    
176      real ztra_th(klon, llm)      real ztra_th(klon, llm)
177      integer isplit      integer isplit, varid
178    
179      ! Controls:      ! Controls:
180      logical:: couchelimite = .true.      logical:: couchelimite = .true.
# Line 193  contains Line 197  contains
197    
198         ! Initialisation de certaines variables pour le radon et le plomb         ! Initialisation de certaines variables pour le radon et le plomb
199         ! Initialisation du traceur dans le sol (couche limite radonique)         ! Initialisation du traceur dans le sol (couche limite radonique)
200         trs(:, :) = 0.         trs(:, 2:) = 0.
201    
202         open (unit=99, file='starttrac', status='old', err=999, &         call nf95_inq_varid(ncid_startphy, "trs", varid)
203              form='formatted')         call nf95_get_var(ncid_startphy, varid, trs(:, 1))
        read(unit=99, fmt=*) (trs(i, 1), i=1, klon)  
 999    continue  
        close(unit=99)  
204    
205         ! Initialisation de la fraction d'aerosols lessivee         ! Initialisation de la fraction d'aerosols lessivee
206    
# Line 403  contains Line 404  contains
404      call write_histrac(lessivage, itap, nid_tra)      call write_histrac(lessivage, itap, nid_tra)
405    
406      if (lafin) then      if (lafin) then
407         print *, "C'est la fin de la physique."         call nf95_inq_varid(ncid_restartphy, "trs", varid)
408         open(unit=99, file='restarttrac', form='formatted')         call nf95_put_var(ncid_restartphy, varid, trs(:, 1))
        do i=1, klon  
           write(unit=99, fmt=*) trs(i, 1)  
        enddo  
        PRINT *, 'Ecriture du fichier restarttrac'  
        close(unit=99)  
409      endif      endif
410    
411    contains    contains

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

  ViewVC Help
Powered by ViewVC 1.1.21