/[lmdze]/trunk/libf/phylmd/phytrac.f90
ViewVC logotype

Diff of /trunk/libf/phylmd/phytrac.f90

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

revision 3 by guez, Wed Feb 27 13:16:39 2008 UTC revision 12 by guez, Mon Jul 21 16:05:07 2008 UTC
# Line 9  module phytrac_m Line 9  module phytrac_m
9    
10  contains  contains
11    
12    SUBROUTINE phytrac(rnpb, nstep, julien, gmtime, debutphy, lafin, nqmax, &    SUBROUTINE phytrac(rnpb, itap, lmt_pas, julien, gmtime, firstcal, lafin, &
13         pdtphys, u, v, t_seri, paprs, pplay, pmfu, pmfd, pen_u, &         nqmax, pdtphys, u, v, t_seri, paprs, pplay, pmfu, pmfd, pen_u, &
14         pde_u, pen_d, pde_d, coefh, fm_therm, entr_therm, yu1, yv1, ftsol, &         pde_u, pen_d, pde_d, coefh, fm_therm, entr_therm, yu1, yv1, ftsol, &
15         pctsrf, frac_impa, frac_nucl, presnivs, pphis, &         pctsrf, frac_impa, frac_nucl, presnivs, pphis, &
16         pphi, albsol, sh, rh, cldfra, rneb, diafra, cldliq, itop_con, &         pphi, albsol, rh, cldfra, rneb, diafra, cldliq, itop_con, &
17         ibas_con, pmflxr, pmflxs, prfl, psfl, da, phi, mp, upwd, dnwd, tr_seri)         ibas_con, pmflxr, pmflxs, prfl, psfl, da, phi, mp, upwd, dnwd, tr_seri)
18    
19      ! From phylmd/phytrac.F, version 1.15 2006/02/21 08:08:30      ! From phylmd/phytrac.F, version 1.15 2006/02/21 08:08:30
# Line 33  contains Line 33  contains
33      use dimens_m, only: iim, jjm, llm      use dimens_m, only: iim, jjm, llm
34      use indicesol, only: nbsrf      use indicesol, only: nbsrf
35      use dimphy, only: klon, nbtr      use dimphy, only: klon, nbtr
36      use clesphys, only: ecrit_tra, iflag_con      use clesphys, only: ecrit_tra
37        use clesphys2, only: iflag_con
38      use abort_gcm_m, only: abort_gcm      use abort_gcm_m, only: abort_gcm
39      use YOMCST, only: rg      use YOMCST, only: rg
40      use ctherm, only: iflag_thermals      use ctherm, only: iflag_thermals
41      use read_coefoz_m, only: read_coefoz      use regr_pr_comb_coefoz_m, only: regr_pr_comb_coefoz
42      use phyetat0_m, only: rlat      use phyetat0_m, only: rlat
43      use o3_chem_m, only: o3_chem      use o3_chem_m, only: o3_chem
44    
# Line 52  contains Line 53  contains
53      integer, intent(in):: nqmax      integer, intent(in):: nqmax
54      ! (nombre de traceurs auxquels on applique la physique)      ! (nombre de traceurs auxquels on applique la physique)
55    
56      integer, intent(in):: nstep  ! appel physique      integer, intent(in):: itap  ! number of calls to "physiq"
57        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      integer itop_con(klon)      integer itop_con(klon)
60      integer ibas_con(klon)      integer ibas_con(klon)
61      real, intent(in):: gmtime ! heure de la journée en fraction de jour      real, intent(in):: gmtime ! heure de la journée en fraction de jour
62      real pdtphys  ! pas d'integration pour la physique (s)      real, intent(in):: pdtphys  ! pas d'integration pour la physique (s)
63      real, intent(in):: t_seri(klon, llm) ! temperature, in K      real, intent(in):: t_seri(klon, llm) ! temperature, in K
64    
65      real tr_seri(klon, llm, nbtr)      real tr_seri(klon, llm, nbtr)
# Line 65  contains Line 67  contains
67    
68      real u(klon, llm)      real u(klon, llm)
69      real v(klon, llm)      real v(klon, llm)
     real sh(klon, llm)     ! humidite specifique  
70      real rh(klon, llm)     ! humidite relative      real rh(klon, llm)     ! humidite relative
71      real cldliq(klon, llm) ! eau liquide nuageuse      real cldliq(klon, llm) ! eau liquide nuageuse
72      real cldfra(klon, llm) ! fraction nuageuse (tous les nuages)      real cldfra(klon, llm) ! fraction nuageuse (tous les nuages)
# Line 79  contains Line 80  contains
80      real, intent(in):: paprs(klon, llm+1)      real, intent(in):: paprs(klon, llm+1)
81      ! (pression pour chaque inter-couche, en Pa)      ! (pression pour chaque inter-couche, en Pa)
82    
83      real pplay(klon, llm)  ! pression pour le mileu de chaque couche (en Pa)      real, intent(in):: pplay(klon, llm)
84        ! (pression pour le mileu de chaque couche, en Pa)
85    
86      real pphi(klon, llm) ! geopotentiel      real pphi(klon, llm) ! geopotentiel
87      real pphis(klon)      real pphis(klon)
88      REAL, intent(in):: presnivs(llm)      REAL, intent(in):: presnivs(llm)
89      logical, intent(in):: debutphy ! le flag de l'initialisation de la physique      logical, intent(in):: firstcal ! first call to "calfis"
90      logical, intent(in):: lafin ! fin de la physique      logical, intent(in):: lafin ! fin de la physique
91    
92      integer nsplit      integer nsplit
# Line 208  contains Line 211  contains
211    
212      modname='phytrac'      modname='phytrac'
213    
214      if (debutphy) then      if (firstcal) then
215         print *, 'phytrac: pdtphys = ', pdtphys         print *, 'phytrac: pdtphys = ', pdtphys
216         PRINT *, 'Fréquence de sortie des traceurs : ecrit_tra = ', ecrit_tra         PRINT *, 'Fréquence de sortie des traceurs : ecrit_tra = ', ecrit_tra
217         if (nbtr < nqmax) then         if (nbtr < nqmax) then
# Line 242  contains Line 245  contains
245            radio(it) = .FALSE. ! par défaut pas de passage par "radiornpb"            radio(it) = .FALSE. ! par défaut pas de passage par "radiornpb"
246            clsol(it) = .FALSE.  ! Par defaut couche limite avec flux prescrit            clsol(it) = .FALSE.  ! Par defaut couche limite avec flux prescrit
247         ENDDO         ENDDO
   
        ! Get the parameters for ozone chemistry:  
        call read_coefoz  
248      ENDIF      ENDIF
249    
250      ! Initialisation du traceur dans le sol (couche limite radonique)      ! Initialisation du traceur dans le sol (couche limite radonique)
# Line 281  contains Line 281  contains
281            if (iflag_con.eq.2) then            if (iflag_con.eq.2) then
282               ! tiedke               ! tiedke
283               CALL nflxtr(pdtphys, pmfu, pmfd, pen_u, pde_u, pen_d, pde_d, &               CALL nflxtr(pdtphys, pmfu, pmfd, pen_u, pde_u, pen_d, pde_d, &
284                    pplay, paprs, tr_seri(1, 1, it), d_tr_cv(1, 1, it))                    paprs, tr_seri(1, 1, it), d_tr_cv(1, 1, it))
285            else if (iflag_con.eq.3) then            else if (iflag_con.eq.3) then
286               ! KE               ! KE
287               call cvltr(pdtphys, da, phi, mp, paprs, pplay, &               call cvltr(pdtphys, da, phi, mp, paprs, &
288                    tr_seri(1, 1, it), upwd, dnwd, d_tr_cv(1, 1, it))                    tr_seri(1, 1, it), upwd, dnwd, d_tr_cv(1, 1, it))
289            endif            endif
290    
# Line 401  contains Line 401  contains
401         ENDDO         ENDDO
402      endif ! rnpb decroissance  radioactive      endif ! rnpb decroissance  radioactive
403    
404      ! Ozone as a tracer:      if (nqmax >= 3) then
405      call o3_chem(julien, gmtime, t_seri, zmasse, pdtphys, tr_seri(:, :, 3))         ! Ozone as a tracer:
406           if (mod(itap - 1, lmt_pas) == 0) then
407              ! Once per day, update the coefficients for ozone chemistry:
408              call regr_pr_comb_coefoz(julien)
409           end if
410           call o3_chem(julien, gmtime, t_seri, zmasse, pdtphys, tr_seri(:, :, 3))
411        end if
412    
413      ! Calcul de l'effet de la precipitation      ! Calcul de l'effet de la precipitation
414    
# Line 456  contains Line 462  contains
462      ENDIF      ENDIF
463    
464      !   Ecriture des sorties      !   Ecriture des sorties
465      call write_histrac(lessivage, nqmax, nstep, nid_tra)      call write_histrac(lessivage, nqmax, itap, nid_tra)
466    
467      if (lafin) then      if (lafin) then
468         print *, "C'est la fin de la physique."         print *, "C'est la fin de la physique."
# Line 470  contains Line 476  contains
476    
477    contains    contains
478    
479      subroutine write_histrac(lessivage, nqmax, nstep, nid_tra)      subroutine write_histrac(lessivage, nqmax, itap, nid_tra)
480    
481        ! 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
482    
# Line 486  contains Line 492  contains
492        integer, intent(in):: nqmax        integer, intent(in):: nqmax
493        ! (nombre de traceurs auxquels on applique la physique)        ! (nombre de traceurs auxquels on applique la physique)
494    
495        integer, intent(in):: nstep  ! appel physique        integer, intent(in):: itap  ! number of calls to "physiq"
496        integer, intent(in):: nid_tra        integer, intent(in):: nid_tra
497    
498        ! Variables local to the procedure:        ! Variables local to the procedure:
# Line 500  contains Line 506  contains
506    
507        ndex2d = 0        ndex2d = 0
508        ndex3d = 0        ndex3d = 0
509        itau_w = itau_phy + nstep        itau_w = itau_phy + itap
510    
511        CALL gr_fi_ecrit(1, klon, iim, jjm+1, pphis, zx_tmp_2d)        CALL gr_fi_ecrit(1, klon, iim, jjm+1, pphis, zx_tmp_2d)
512        CALL histwrite(nid_tra, "phis", itau_w, zx_tmp_2d, iim*(jjm+1), ndex2d)        CALL histwrite(nid_tra, "phis", itau_w, zx_tmp_2d, iim*(jjm+1), ndex2d)

Legend:
Removed from v.3  
changed lines
  Added in v.12

  ViewVC Help
Powered by ViewVC 1.1.21