/[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 17 by guez, Tue Aug 5 13:31:32 2008 UTC revision 18 by guez, Thu Aug 7 12:29:13 2008 UTC
# Line 10  module phytrac_m Line 10  module phytrac_m
10  contains  contains
11    
12    SUBROUTINE phytrac(rnpb, itap, lmt_pas, julien, gmtime, firstcal, lafin, &    SUBROUTINE phytrac(rnpb, itap, lmt_pas, julien, gmtime, firstcal, lafin, &
13         nqmax, pdtphys, u, v, t_seri, paprs, pplay, pmfu, pmfd, pen_u, &         nq_phys, 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, rh, cldfra, rneb, diafra, cldliq, itop_con, &         pphi, albsol, rh, cldfra, rneb, diafra, cldliq, itop_con, &
# Line 19  contains Line 19  contains
19    
20      ! 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
21    
22      ! Authors : Frédéric Hourdin, Abderrahmane Idelkadi, Marie-Alice      ! Authors: Frédéric Hourdin, Abderrahmane Idelkadi, Marie-Alice
23      ! Foujols, Olivia      ! Foujols, Olivia
24      ! Objet : moniteur général des tendances des traceurs      ! Objet : moniteur général des tendances des traceurs
25    
# Line 56  contains Line 56  contains
56    
57      logical, intent(in):: rnpb      logical, intent(in):: rnpb
58    
59      integer, intent(in):: nqmax      integer, intent(in):: nq_phys
60      ! (nombre de traceurs auxquels on applique la physique)      ! (nombre de traceurs auxquels on applique la physique)
61    
62      integer, intent(in):: itap  ! number of calls to "physiq"      integer, intent(in):: itap  ! number of calls to "physiq"
# Line 68  contains Line 68  contains
68      real, intent(in):: pdtphys  ! pas d'integration pour la physique (s)      real, intent(in):: pdtphys  ! pas d'integration pour la physique (s)
69      real, intent(in):: t_seri(klon, llm) ! temperature, in K      real, intent(in):: t_seri(klon, llm) ! temperature, in K
70    
71      real, intent(inout):: tr_seri(klon, llm, nbtr)      real, intent(inout):: tr_seri(:, :, :) ! (klon, llm, nbtr)
72      ! (mass fractions of tracers, excluding water, at mid-layers)      ! (mass fractions of tracers, excluding water, at mid-layers)
73    
74      real u(klon, llm)      real u(klon, llm)
# Line 211  contains Line 211  contains
211    
212      !--------------------------------------      !--------------------------------------
213    
214      call assert(shape(zmasse) == (/klon, llm/), "phytrac")      call assert(shape(zmasse) == (/klon, llm/), "phytrac zmasse")
215        call assert(shape(tr_seri) == (/klon, llm, nbtr/), "phytrac tr_seri")
216    
217      if (firstcal) then      if (firstcal) then
218         print *, 'phytrac: pdtphys = ', pdtphys         print *, 'phytrac: pdtphys = ', pdtphys
219         PRINT *, 'Fréquence de sortie des traceurs : ecrit_tra = ', ecrit_tra         PRINT *, 'Fréquence de sortie des traceurs : ecrit_tra = ', ecrit_tra
220         if (nbtr < nqmax) call abort_gcm('phytrac', 'See above', 1)         if (nbtr < nq_phys) call abort_gcm('phytrac', 'nbtr < nq_phys', 1)
221         inirnpb=rnpb         inirnpb=rnpb
222    
223         ! Initialisation des sorties :         ! Initialisation des sorties :
224         call ini_histrac(nid_tra, pdtphys, presnivs, nqmax, lessivage)         call ini_histrac(nid_tra, pdtphys, presnivs, nq_phys, lessivage)
225    
226         ! Initialisation de certaines variables pour le radon et le plomb         ! Initialisation de certaines variables pour le radon et le plomb
227         ! Initialisation du traceur dans le sol (couche limite radonique)         ! Initialisation du traceur dans le sol (couche limite radonique)
# Line 239  contains Line 240  contains
240    
241         ! Initialisation de la nature des traceurs         ! Initialisation de la nature des traceurs
242    
243         DO it = 1, nqmax         DO it = 1, nq_phys
244            aerosol(it) = .FALSE.  ! Tous les traceurs sont des gaz par defaut            aerosol(it) = .FALSE.  ! Tous les traceurs sont des gaz par defaut
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
248    
249         if (nqmax >= 3) then         if (nq_phys >= 3) then
250            call press_coefoz ! read input pressure levels for ozone coefficients            call press_coefoz ! read input pressure levels for ozone coefficients
251         end if         end if
252      ENDIF      ENDIF
# Line 267  contains Line 268  contains
268      ! Calcul de l'effet de la convection      ! Calcul de l'effet de la convection
269    
270      if (convection) then      if (convection) then
271         DO it=1, nqmax         DO it=1, nq_phys
272            if (iflag_con.eq.2) then            if (iflag_con.eq.2) then
273               ! tiedke               ! tiedke
274               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, &
# Line 291  contains Line 292  contains
292    
293      ! Calcul de l'effet des thermiques      ! Calcul de l'effet des thermiques
294    
295      do it=1, nqmax      do it=1, nq_phys
296         do k=1, llm         do k=1, llm
297            do i=1, klon            do i=1, klon
298               d_tr_th(i, k, it)=0.               d_tr_th(i, k, it)=0.
# Line 303  contains Line 304  contains
304    
305      if (iflag_thermals > 0) then      if (iflag_thermals > 0) then
306         nsplit=10         nsplit=10
307         DO it=1, nqmax         DO it=1, nq_phys
308            do isplit=1, nsplit            do isplit=1, nsplit
309               ! Thermiques               ! Thermiques
310               call dqthermcell(klon, llm, pdtphys/nsplit &               call dqthermcell(klon, llm, pdtphys/nsplit &
# Line 332  contains Line 333  contains
333         ENDDO         ENDDO
334    
335         ! MAF modif pour tenir compte du cas rnpb + traceur         ! MAF modif pour tenir compte du cas rnpb + traceur
336         DO it=1, nqmax         DO it=1, nq_phys
337            if (clsol(it)) then            if (clsol(it)) then
338               ! couche limite avec quantite dans le sol calculee               ! couche limite avec quantite dans le sol calculee
339               CALL cltracrn(it, pdtphys, yu1, yv1, &               CALL cltracrn(it, pdtphys, yu1, yv1, &
# Line 380  contains Line 381  contains
381      ! si radio=true mais pour l'instant radiornpb propre au cas rnpb      ! si radio=true mais pour l'instant radiornpb propre au cas rnpb
382      if (rnpb) then      if (rnpb) then
383         d_tr_dec(:, :, :) = radiornpb(tr_seri, pdtphys, tautr)         d_tr_dec(:, :, :) = radiornpb(tr_seri, pdtphys, tautr)
384         DO it=1, nqmax         DO it=1, nq_phys
385            if (radio(it)) then            if (radio(it)) then
386               tr_seri(:, :, it) = tr_seri(:, :, it) + d_tr_dec(:, :, it)               tr_seri(:, :, it) = tr_seri(:, :, it) + d_tr_dec(:, :, it)
387               WRITE(unit=itn, fmt='(i1)') it               WRITE(unit=itn, fmt='(i1)') it
# Line 389  contains Line 390  contains
390         ENDDO         ENDDO
391      endif ! rnpb decroissance  radioactive      endif ! rnpb decroissance  radioactive
392    
393      if (nqmax >= 3) then      if (nq_phys >= 3) then
394         ! Ozone as a tracer:         ! Ozone as a tracer:
395         if (mod(itap - 1, lmt_pas) == 0) then         if (mod(itap - 1, lmt_pas) == 0) then
396            ! Once per day, update the coefficients for ozone chemistry:            ! Once per day, update the coefficients for ozone chemistry:
# Line 407  contains Line 408  contains
408    
409         ! tendance des aerosols nuclees et impactes         ! tendance des aerosols nuclees et impactes
410    
411         DO it = 1, nqmax         DO it = 1, nq_phys
412            IF (aerosol(it)) THEN            IF (aerosol(it)) THEN
413               DO k = 1, llm               DO k = 1, llm
414                  DO i = 1, klon                  DO i = 1, klon
# Line 423  contains Line 424  contains
424         ! Mises a jour des traceurs + calcul des flux de lessivage         ! Mises a jour des traceurs + calcul des flux de lessivage
425         ! Mise a jour due a l'impaction et a la nucleation         ! Mise a jour due a l'impaction et a la nucleation
426    
427         DO it = 1, nqmax         DO it = 1, nq_phys
428            IF (aerosol(it)) THEN            IF (aerosol(it)) THEN
429               DO k = 1, llm               DO k = 1, llm
430                  DO i = 1, klon                  DO i = 1, klon
# Line 436  contains Line 437  contains
437    
438         ! Flux lessivage total         ! Flux lessivage total
439    
440         DO it = 1, nqmax         DO it = 1, nq_phys
441            DO k = 1, llm            DO k = 1, llm
442               DO i = 1, klon               DO i = 1, klon
443                  flestottr(i, k, it) = flestottr(i, k, it) - &                  flestottr(i, k, it) = flestottr(i, k, it) - &
# Line 450  contains Line 451  contains
451      ENDIF      ENDIF
452    
453      !   Ecriture des sorties      !   Ecriture des sorties
454      call write_histrac(lessivage, nqmax, itap, nid_tra)      call write_histrac(lessivage, nq_phys, itap, nid_tra)
455    
456      if (lafin) then      if (lafin) then
457         print *, "C'est la fin de la physique."         print *, "C'est la fin de la physique."
# Line 464  contains Line 465  contains
465    
466    contains    contains
467    
468      subroutine write_histrac(lessivage, nqmax, itap, nid_tra)      subroutine write_histrac(lessivage, nq_phys, itap, nid_tra)
469    
470        ! 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
471    
472        use dimens_m, only: iim, jjm, llm        use dimens_m, only: iim, jjm, llm
473        use ioipsl, only: histwrite, histsync        use ioipsl, only: histwrite, histsync
474        use temps, only: itau_phy        use temps, only: itau_phy
475        use advtrac_m, only: tnom        use iniadvtrac_m, only: tnom
476        use comgeomphy, only: airephy        use comgeomphy, only: airephy
477        use dimphy, only: klon        use dimphy, only: klon
478    
479        logical, intent(in):: lessivage        logical, intent(in):: lessivage
480    
481        integer, intent(in):: nqmax        integer, intent(in):: nq_phys
482        ! (nombre de traceurs auxquels on applique la physique)        ! (nombre de traceurs auxquels on applique la physique)
483    
484        integer, intent(in):: itap  ! number of calls to "physiq"        integer, intent(in):: itap  ! number of calls to "physiq"
# Line 502  contains Line 503  contains
503        CALL gr_fi_ecrit(llm, klon, iim, jjm+1, zmasse, zx_tmp_3d)              CALL gr_fi_ecrit(llm, klon, iim, jjm+1, zmasse, zx_tmp_3d)      
504        CALL histwrite(nid_tra, "zmasse", itau_w, zx_tmp_3d)        CALL histwrite(nid_tra, "zmasse", itau_w, zx_tmp_3d)
505    
506        DO it=1, nqmax        DO it=1, nq_phys
507           CALL gr_fi_ecrit(llm, klon, iim, jjm+1, tr_seri(1, 1, it), zx_tmp_3d)           CALL gr_fi_ecrit(llm, klon, iim, jjm+1, tr_seri(1, 1, it), zx_tmp_3d)
508           CALL histwrite(nid_tra, tnom(it+2), itau_w, zx_tmp_3d)           CALL histwrite(nid_tra, tnom(it+2), itau_w, zx_tmp_3d)
509           if (lessivage) THEN           if (lessivage) THEN

Legend:
Removed from v.17  
changed lines
  Added in v.18

  ViewVC Help
Powered by ViewVC 1.1.21