/[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 118 by guez, Thu Dec 18 17:30:24 2014 UTC trunk/Sources/phylmd/phytrac.f revision 182 by guez, Wed Mar 16 11:11:27 2016 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)         mp, upwd, dnwd, tr_seri, zmasse, ncid_startphy, nid_ins, itau_phy)
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 28  contains Line 28  contains
28    
29      use abort_gcm_m, only: abort_gcm      use abort_gcm_m, only: abort_gcm
30      use clesphys, only: ecrit_tra      use clesphys, only: ecrit_tra
31      use clesphys2, only: iflag_con      use clesphys2, only: conv_emanuel
32        use cltrac_m, only: cltrac
33      use cltracrn_m, only: cltracrn      use cltracrn_m, only: cltracrn
34      use ctherm, only: iflag_thermals      use ctherm, only: iflag_thermals
35        use cvltr_m, only: cvltr
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 netcdf, only: NF90_FILL_float
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 87  contains Line 91  contains
91      REAL frac_impa(klon, llm) ! fraction d'aerosols impactes      REAL frac_impa(klon, llm) ! fraction d'aerosols impactes
92      REAL frac_nucl(klon, llm) ! fraction d'aerosols nuclees      REAL frac_nucl(klon, llm) ! fraction d'aerosols nuclees
93    
     real, intent(in):: pphis(klon)  
   
94      ! Kerry Emanuel      ! Kerry Emanuel
95      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)
96      REAL, intent(in):: upwd(klon, llm) ! saturated updraft mass flux      REAL, intent(in):: upwd(klon, llm) ! saturated updraft mass flux
# Line 100  contains Line 102  contains
102      real, intent(in):: zmasse(:, :) ! (klon, llm)      real, intent(in):: zmasse(:, :) ! (klon, llm)
103      ! (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)
104    
105      ! Variables local to the procedure:      integer, intent(in):: ncid_startphy, nid_ins, itau_phy
106    
107        ! Local:
108    
109      integer nsplit      integer nsplit
110    
# Line 114  contains Line 118  contains
118      !      !
119      ! Pour la source de radon et son reservoir de sol      ! Pour la source de radon et son reservoir de sol
120    
121      REAL, save:: trs(klon, nqmx - 2) ! Concentration de radon dans le sol      REAL, save:: trs(klon, nqmx - 2) ! Concentration de traceur dans le sol
122    
123      REAL masktr(klon, nqmx - 2) ! Masque reservoir de sol traceur      REAL masktr(klon, nqmx - 2) ! Masque reservoir de sol traceur
124      ! Masque de l'echange avec la surface      ! Masque de l'echange avec la surface
# Line 132  contains Line 136  contains
136      SAVE scavtr      SAVE scavtr
137    
138      CHARACTER itn      CHARACTER itn
     INTEGER, save:: nid_tra  
139    
140      ! nature du traceur      ! nature du traceur
141    
# Line 153  contains Line 156  contains
156    
157      REAL d_tr(klon, llm), d_trs(klon) ! tendances de traceurs      REAL d_tr(klon, llm), d_trs(klon) ! tendances de traceurs
158      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
159      REAL d_tr_cv(klon, llm, nqmx - 2) ! tendance de traceurs conv pour chq traceur  
160        REAL d_tr_cv(klon, llm, nqmx - 2)
161        ! tendance de traceurs conv pour chq traceur
162    
163      REAL d_tr_th(klon, llm, nqmx - 2) ! la tendance des thermiques      REAL d_tr_th(klon, llm, nqmx - 2) ! la tendance des thermiques
164      REAL d_tr_dec(klon, llm, 2) ! la tendance de la decroissance      REAL d_tr_dec(klon, llm, 2) ! la tendance de la decroissance
165      ! ! radioactive du rn - > pb      ! ! radioactive du rn - > pb
# Line 165  contains Line 171  contains
171      ! ! dans chaque couche      ! ! dans chaque couche
172    
173      real ztra_th(klon, llm)      real ztra_th(klon, llm)
174      integer isplit      integer isplit, varid
175    
176      ! Controls:      ! Controls:
177      logical:: couchelimite = .true.      logical:: couchelimite = .true.
# Line 183  contains Line 189  contains
189         PRINT *, 'Frequency of tracer output: ecrit_tra = ', ecrit_tra         PRINT *, 'Frequency of tracer output: ecrit_tra = ', ecrit_tra
190         inirnpb = .true.         inirnpb = .true.
191    
        ! Initialisation des sorties :  
        call ini_histrac(nid_tra, pdtphys, nqmx - 2, lessivage)  
   
192         ! Initialisation de certaines variables pour le radon et le plomb         ! Initialisation de certaines variables pour le radon et le plomb
193         ! Initialisation du traceur dans le sol (couche limite radonique)         ! Initialisation du traceur dans le sol (couche limite radonique)
194         trs(:, :) = 0.         trs(:, 2:) = 0.
195    
196         open (unit=99, file='starttrac', status='old', err=999, &         call nf95_inq_varid(ncid_startphy, "trs", varid)
197              form='formatted')         call nf95_get_var(ncid_startphy, varid, trs(:, 1))
198         read(unit=99, fmt=*) (trs(i, 1), i=1, klon)         if (any(trs(:, 1) == NF90_FILL_float)) call abort_gcm("phytrac", &
199  999    continue              "some missing values in trs(:, 1)")
        close(unit=99)  
200    
201         ! Initialisation de la fraction d'aerosols lessivee         ! Initialisation de la fraction d'aerosols lessivee
202    
# Line 228  contains Line 230  contains
230      if (convection) then      if (convection) then
231         ! Calcul de l'effet de la convection         ! Calcul de l'effet de la convection
232         DO it=1, nqmx - 2         DO it=1, nqmx - 2
233            if (iflag_con == 2) then            if (conv_emanuel) then
234               ! Tiedke               call cvltr(pdtphys, da, phi, mp, paprs, tr_seri(:, :, it), upwd, &
235                      dnwd, d_tr_cv(:, :, it))
236              else
237               CALL nflxtr(pdtphys, pmfu, pmfd, pde_u, pen_d, paprs, &               CALL nflxtr(pdtphys, pmfu, pmfd, pde_u, pen_d, paprs, &
238                    tr_seri(:, :, it), d_tr_cv(:, :, it))                    tr_seri(:, :, it), d_tr_cv(:, :, it))
           else if (iflag_con == 3) then  
              ! Emanuel  
              call cvltr(pdtphys, da, phi, mp, paprs, tr_seri(1, 1, it), upwd, &  
                   dnwd, d_tr_cv(1, 1, it))  
239            endif            endif
240    
241            DO k = 1, llm            DO k = 1, llm
# Line 294  contains Line 294  contains
294         DO it=1, nqmx - 2         DO it=1, nqmx - 2
295            if (clsol(it)) then            if (clsol(it)) then
296               ! couche limite avec quantite dans le sol calculee               ! couche limite avec quantite dans le sol calculee
297               CALL cltracrn(it, pdtphys, yu1, yv1, &               CALL cltracrn(it, pdtphys, yu1, yv1, coefh, t_seri, ftsol, &
298                    coefh, t_seri, ftsol, pctsrf, &                    pctsrf, tr_seri(:, :, it), trs(:, it), paprs, pplay, delp, &
299                    tr_seri(:, :, it), trs(1, it), &                    masktr(1, it), fshtr(1, it), hsoltr(it), tautr(it), &
300                    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)  
301               DO k = 1, llm               DO k = 1, llm
302                  DO i = 1, klon                  DO i = 1, klon
303                     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)
304                  ENDDO                  ENDDO
305               ENDDO               ENDDO
306    
307               ! Traceur ds sol               trs(:, it) = trs(:, it) + d_trs
308              else
309               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  
310               !MAF provisoire source / traceur a creer               !MAF provisoire source / traceur a creer
311               DO i=1, klon               DO i=1, klon
312                  source(i) = 0.0 ! pas de source, pour l'instant                  source(i) = 0. ! pas de source, pour l'instant
313               ENDDO               ENDDO
314    
315               CALL cltrac(pdtphys, coefh, t_seri, &               CALL cltrac(pdtphys, coefh, t_seri, tr_seri(:, :, it), source, &
316                    tr_seri(1, 1, it), source, &                    paprs, pplay, delp, d_tr_cl(1, 1, it))
                   paprs, pplay, delp, &  
                   d_tr_cl(1, 1, it))  
317               DO k = 1, llm               DO k = 1, llm
318                  DO i = 1, klon                  DO i = 1, klon
319                     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)
# Line 349  contains Line 340  contains
340         ! Ozone as a tracer:         ! Ozone as a tracer:
341         if (mod(itap - 1, lmt_pas) == 0) then         if (mod(itap - 1, lmt_pas) == 0) then
342            ! Once per day, update the coefficients for ozone chemistry:            ! Once per day, update the coefficients for ozone chemistry:
343            call regr_pr_comb_coefoz(julien)            call regr_pr_comb_coefoz(julien, paprs, pplay)
344         end if         end if
345         call o3_chem(julien, gmtime, t_seri, zmasse, pdtphys, tr_seri(:, :, 3))         call o3_chem(julien, gmtime, t_seri, zmasse, pdtphys, tr_seri(:, :, 3))
346      end if      end if
# Line 404  contains Line 395  contains
395      ENDIF      ENDIF
396    
397      ! Ecriture des sorties      ! Ecriture des sorties
398      call write_histrac(lessivage, itap, nid_tra)      call write_histrac(lessivage, itap, nid_ins)
399    
400      if (lafin) then      if (lafin) then
401         print *, "C'est la fin de la physique."         call nf95_inq_varid(ncid_restartphy, "trs", varid)
402         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)  
403      endif      endif
404    
405    contains    contains
406    
407      subroutine write_histrac(lessivage, itap, nid_tra)      subroutine write_histrac(lessivage, itap, nid_ins)
408    
409        ! 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
410    
       use dimens_m, only: iim, jjm, llm  
       use histsync_m, only: histsync  
411        use histwrite_m, only: histwrite        use histwrite_m, only: histwrite
412        use temps, only: itau_phy        use iniadvtrac_m, only: tname
       use iniadvtrac_m, only: tnom  
       use comgeomphy, only: airephy  
       use dimphy, only: klon  
       use grid_change, only: gr_phy_write_2d  
413        use gr_phy_write_3d_m, only: gr_phy_write_3d        use gr_phy_write_3d_m, only: gr_phy_write_3d
414    
415        logical, intent(in):: lessivage        logical, intent(in):: lessivage
416        integer, intent(in):: itap ! number of calls to "physiq"        integer, intent(in):: itap ! number of calls to "physiq"
417        integer, intent(in):: nid_tra        integer, intent(in):: nid_ins
418    
419        ! Variables local to the procedure:        ! Variables local to the procedure:
420        integer it        integer it
421        integer itau_w ! pas de temps ecriture        integer itau_w ! pas de temps ecriture
       logical, parameter:: ok_sync = .true.  
422    
423        !-----------------------------------------------------        !-----------------------------------------------------
424    
425        itau_w = itau_phy + itap        itau_w = itau_phy + itap
426    
427        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))  
428    
429        DO it=1, nqmx - 2        DO it=1, nqmx - 2
430           CALL histwrite(nid_tra, tnom(it+2), itau_w, &           CALL histwrite(nid_ins, tname(it+2), itau_w, &
431                gr_phy_write_3d(tr_seri(:, :, it)))                gr_phy_write_3d(tr_seri(:, :, it)))
432           if (lessivage) THEN           if (lessivage) THEN
433              CALL histwrite(nid_tra, "fl"//tnom(it+2), itau_w, &              CALL histwrite(nid_ins, "fl"//tname(it+2), itau_w, &
434                   gr_phy_write_3d(flestottr(:, :, it)))                   gr_phy_write_3d(flestottr(:, :, it)))
435           endif           endif
436           CALL histwrite(nid_tra, "d_tr_th_"//tnom(it+2), itau_w, &           CALL histwrite(nid_ins, "d_tr_th_"//tname(it+2), itau_w, &
437                gr_phy_write_3d(d_tr_th(:, :, it)))                gr_phy_write_3d(d_tr_th(:, :, it)))
438           CALL histwrite(nid_tra, "d_tr_cv_"//tnom(it+2), itau_w, &           CALL histwrite(nid_ins, "d_tr_cv_"//tname(it+2), itau_w, &
439                gr_phy_write_3d(d_tr_cv(:, :, it)))                gr_phy_write_3d(d_tr_cv(:, :, it)))
440           CALL histwrite(nid_tra, "d_tr_cl_"//tnom(it+2), itau_w, &           CALL histwrite(nid_ins, "d_tr_cl_"//tname(it+2), itau_w, &
441                gr_phy_write_3d(d_tr_cl(:, :, it)))                gr_phy_write_3d(d_tr_cl(:, :, it)))
442        ENDDO        ENDDO
443    
       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  
   
444      end subroutine write_histrac      end subroutine write_histrac
445    
446    END SUBROUTINE phytrac    END SUBROUTINE phytrac

Legend:
Removed from v.118  
changed lines
  Added in v.182

  ViewVC Help
Powered by ViewVC 1.1.21