/[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 120 by guez, Tue Jan 13 14:56:15 2015 UTC trunk/Sources/phylmd/phytrac.f 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 116  contains Line 120  contains
120      !      !
121      ! Pour la source de radon et son reservoir de sol      ! Pour la source de radon et son reservoir de sol
122    
123      REAL, save:: trs(klon, nqmx - 2) ! Concentration de radon dans le sol      REAL, save:: trs(klon, nqmx - 2) ! Concentration de traceur dans le sol
124    
125      REAL masktr(klon, nqmx - 2) ! Masque reservoir de sol traceur      REAL masktr(klon, nqmx - 2) ! Masque reservoir de sol traceur
126      ! Masque de l'echange avec la surface      ! Masque de l'echange avec la surface
# Line 155  contains Line 159  contains
159    
160      REAL d_tr(klon, llm), d_trs(klon) ! tendances de traceurs      REAL d_tr(klon, llm), d_trs(klon) ! tendances de traceurs
161      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
162      REAL d_tr_cv(klon, llm, nqmx - 2) ! tendance de traceurs conv pour chq traceur  
163        REAL d_tr_cv(klon, llm, nqmx - 2)
164        ! tendance de traceurs conv pour chq traceur
165    
166      REAL d_tr_th(klon, llm, nqmx - 2) ! la tendance des thermiques      REAL d_tr_th(klon, llm, nqmx - 2) ! la tendance des thermiques
167      REAL d_tr_dec(klon, llm, 2) ! la tendance de la decroissance      REAL d_tr_dec(klon, llm, 2) ! la tendance de la decroissance
168      ! ! radioactive du rn - > pb      ! ! radioactive du rn - > pb
# Line 167  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 190  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 296  contains Line 300  contains
300         DO it=1, nqmx - 2         DO it=1, nqmx - 2
301            if (clsol(it)) then            if (clsol(it)) then
302               ! couche limite avec quantite dans le sol calculee               ! couche limite avec quantite dans le sol calculee
303               CALL cltracrn(it, pdtphys, yu1, yv1, &               CALL cltracrn(it, pdtphys, yu1, yv1, coefh, t_seri, ftsol, &
304                    coefh, t_seri, ftsol, pctsrf, &                    pctsrf, tr_seri(:, :, it), trs(:, it), paprs, pplay, delp, &
305                    tr_seri(:, :, it), trs(1, it), &                    masktr(1, it), fshtr(1, it), hsoltr(it), tautr(it), &
306                    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)  
307               DO k = 1, llm               DO k = 1, llm
308                  DO i = 1, klon                  DO i = 1, klon
309                     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)
310                  ENDDO                  ENDDO
311               ENDDO               ENDDO
312    
313               ! Traceur ds sol               trs(:, it) = trs(:, it) + d_trs
314              else
315               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  
316               !MAF provisoire source / traceur a creer               !MAF provisoire source / traceur a creer
317               DO i=1, klon               DO i=1, klon
318                  source(i) = 0.0 ! pas de source, pour l'instant                  source(i) = 0. ! pas de source, pour l'instant
319               ENDDO               ENDDO
320    
321               CALL cltrac(pdtphys, coefh, t_seri, tr_seri(:, :, it), source, &               CALL cltrac(pdtphys, coefh, t_seri, tr_seri(:, :, it), source, &
# Line 407  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
# Line 426  contains Line 418  contains
418        use histsync_m, only: histsync        use histsync_m, only: histsync
419        use histwrite_m, only: histwrite        use histwrite_m, only: histwrite
420        use temps, only: itau_phy        use temps, only: itau_phy
421        use iniadvtrac_m, only: tnom        use iniadvtrac_m, only: tname
422        use comgeomphy, only: airephy        use comgeomphy, only: airephy
423        use dimphy, only: klon        use dimphy, only: klon
424        use grid_change, only: gr_phy_write_2d        use grid_change, only: gr_phy_write_2d
# Line 450  contains Line 442  contains
442        CALL histwrite(nid_tra, "zmasse", itau_w, gr_phy_write_3d(zmasse))        CALL histwrite(nid_tra, "zmasse", itau_w, gr_phy_write_3d(zmasse))
443    
444        DO it=1, nqmx - 2        DO it=1, nqmx - 2
445           CALL histwrite(nid_tra, tnom(it+2), itau_w, &           CALL histwrite(nid_tra, tname(it+2), itau_w, &
446                gr_phy_write_3d(tr_seri(:, :, it)))                gr_phy_write_3d(tr_seri(:, :, it)))
447           if (lessivage) THEN           if (lessivage) THEN
448              CALL histwrite(nid_tra, "fl"//tnom(it+2), itau_w, &              CALL histwrite(nid_tra, "fl"//tname(it+2), itau_w, &
449                   gr_phy_write_3d(flestottr(:, :, it)))                   gr_phy_write_3d(flestottr(:, :, it)))
450           endif           endif
451           CALL histwrite(nid_tra, "d_tr_th_"//tnom(it+2), itau_w, &           CALL histwrite(nid_tra, "d_tr_th_"//tname(it+2), itau_w, &
452                gr_phy_write_3d(d_tr_th(:, :, it)))                gr_phy_write_3d(d_tr_th(:, :, it)))
453           CALL histwrite(nid_tra, "d_tr_cv_"//tnom(it+2), itau_w, &           CALL histwrite(nid_tra, "d_tr_cv_"//tname(it+2), itau_w, &
454                gr_phy_write_3d(d_tr_cv(:, :, it)))                gr_phy_write_3d(d_tr_cv(:, :, it)))
455           CALL histwrite(nid_tra, "d_tr_cl_"//tnom(it+2), itau_w, &           CALL histwrite(nid_tra, "d_tr_cl_"//tname(it+2), itau_w, &
456                gr_phy_write_3d(d_tr_cl(:, :, it)))                gr_phy_write_3d(d_tr_cl(:, :, it)))
457        ENDDO        ENDDO
458    

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

  ViewVC Help
Powered by ViewVC 1.1.21