/[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 6 by guez, Tue Mar 4 14:00:42 2008 UTC revision 7 by guez, Mon Mar 31 12:24:17 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, sh, rh, cldfra, rneb, diafra, cldliq, itop_con, &
# Line 37  contains Line 37  contains
37      use abort_gcm_m, only: abort_gcm      use abort_gcm_m, only: abort_gcm
38      use YOMCST, only: rg      use YOMCST, only: rg
39      use ctherm, only: iflag_thermals      use ctherm, only: iflag_thermals
40      use read_coefoz_m, only: read_coefoz      use regr_pr_comb_coefoz_m, only: regr_pr_comb_coefoz
41      use phyetat0_m, only: rlat      use phyetat0_m, only: rlat
42      use o3_chem_m, only: o3_chem      use o3_chem_m, only: o3_chem
43    
# Line 52  contains Line 52  contains
52      integer, intent(in):: nqmax      integer, intent(in):: nqmax
53      ! (nombre de traceurs auxquels on applique la physique)      ! (nombre de traceurs auxquels on applique la physique)
54    
55      integer, intent(in):: nstep  ! appel physique      integer, intent(in):: itap  ! number of calls to "physiq"
56        integer, intent(in):: lmt_pas ! number of time steps of "physics" per day
57      integer, intent(in):: julien !jour julien, 1 <= julien <= 360      integer, intent(in):: julien !jour julien, 1 <= julien <= 360
58      integer itop_con(klon)      integer itop_con(klon)
59      integer ibas_con(klon)      integer ibas_con(klon)
60      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
61      real pdtphys  ! pas d'integration pour la physique (s)      real, intent(in):: pdtphys  ! pas d'integration pour la physique (s)
62      real, intent(in):: t_seri(klon, llm) ! temperature, in K      real, intent(in):: t_seri(klon, llm) ! temperature, in K
63    
64      real tr_seri(klon, llm, nbtr)      real tr_seri(klon, llm, nbtr)
# Line 83  contains Line 84  contains
84      real pphi(klon, llm) ! geopotentiel      real pphi(klon, llm) ! geopotentiel
85      real pphis(klon)      real pphis(klon)
86      REAL, intent(in):: presnivs(llm)      REAL, intent(in):: presnivs(llm)
87      logical, intent(in):: debutphy ! le flag de l'initialisation de la physique      logical, intent(in):: firstcal ! first call to "calfis"
88      logical, intent(in):: lafin ! fin de la physique      logical, intent(in):: lafin ! fin de la physique
89    
90      integer nsplit      integer nsplit
# Line 208  contains Line 209  contains
209    
210      modname='phytrac'      modname='phytrac'
211    
212      if (debutphy) then      if (firstcal) then
213         print *, 'phytrac: pdtphys = ', pdtphys         print *, 'phytrac: pdtphys = ', pdtphys
214         PRINT *, 'Fréquence de sortie des traceurs : ecrit_tra = ', ecrit_tra         PRINT *, 'Fréquence de sortie des traceurs : ecrit_tra = ', ecrit_tra
215         if (nbtr < nqmax) then         if (nbtr < nqmax) then
# Line 242  contains Line 243  contains
243            radio(it) = .FALSE. ! par défaut pas de passage par "radiornpb"            radio(it) = .FALSE. ! par défaut pas de passage par "radiornpb"
244            clsol(it) = .FALSE.  ! Par defaut couche limite avec flux prescrit            clsol(it) = .FALSE.  ! Par defaut couche limite avec flux prescrit
245         ENDDO         ENDDO
   
        if (nqmax >= 3) then  
           ! Get the parameters for ozone chemistry:  
           call read_coefoz  
        end if  
246      ENDIF      ENDIF
247    
248      ! Initialisation du traceur dans le sol (couche limite radonique)      ! Initialisation du traceur dans le sol (couche limite radonique)
# Line 405  contains Line 401  contains
401    
402      if (nqmax >= 3) then      if (nqmax >= 3) then
403         ! Ozone as a tracer:         ! Ozone as a tracer:
404           if (mod(itap - 1, lmt_pas) == 0) then
405              ! Once per day, update the coefficients for ozone chemistry:
406              call regr_pr_comb_coefoz(julien)
407           end if
408         call o3_chem(julien, gmtime, t_seri, zmasse, pdtphys, tr_seri(:, :, 3))         call o3_chem(julien, gmtime, t_seri, zmasse, pdtphys, tr_seri(:, :, 3))
409      end if      end if
410    
# Line 460  contains Line 460  contains
460      ENDIF      ENDIF
461    
462      !   Ecriture des sorties      !   Ecriture des sorties
463      call write_histrac(lessivage, nqmax, nstep, nid_tra)      call write_histrac(lessivage, nqmax, itap, nid_tra)
464    
465      if (lafin) then      if (lafin) then
466         print *, "C'est la fin de la physique."         print *, "C'est la fin de la physique."
# Line 474  contains Line 474  contains
474    
475    contains    contains
476    
477      subroutine write_histrac(lessivage, nqmax, nstep, nid_tra)      subroutine write_histrac(lessivage, nqmax, itap, nid_tra)
478    
479        ! 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
480    
# Line 490  contains Line 490  contains
490        integer, intent(in):: nqmax        integer, intent(in):: nqmax
491        ! (nombre de traceurs auxquels on applique la physique)        ! (nombre de traceurs auxquels on applique la physique)
492    
493        integer, intent(in):: nstep  ! appel physique        integer, intent(in):: itap  ! number of calls to "physiq"
494        integer, intent(in):: nid_tra        integer, intent(in):: nid_tra
495    
496        ! Variables local to the procedure:        ! Variables local to the procedure:
# Line 504  contains Line 504  contains
504    
505        ndex2d = 0        ndex2d = 0
506        ndex3d = 0        ndex3d = 0
507        itau_w = itau_phy + nstep        itau_w = itau_phy + itap
508    
509        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)
510        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.6  
changed lines
  Added in v.7

  ViewVC Help
Powered by ViewVC 1.1.21