/[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 34 by guez, Wed Jun 2 11:01:12 2010 UTC
# Line 1  Line 1 
1  module phytrac_m  module phytrac_m
2    
   ! This module is clean: no C preprocessor directive, no include line.  
   
3    IMPLICIT none    IMPLICIT none
4    
5    private    private
# Line 10  module phytrac_m Line 8  module phytrac_m
8  contains  contains
9    
10    SUBROUTINE phytrac(rnpb, itap, lmt_pas, julien, gmtime, firstcal, lafin, &    SUBROUTINE phytrac(rnpb, itap, lmt_pas, julien, gmtime, firstcal, lafin, &
11         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, &
12         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, &
13         pctsrf, frac_impa, frac_nucl, presnivs, pphis, &         pctsrf, frac_impa, frac_nucl, pphis, pphi, albsol, rh, cldfra, rneb, &
14         pphi, albsol, rh, cldfra, rneb, diafra, cldliq, itop_con, &         diafra, cldliq, pmflxr, pmflxs, prfl, psfl, da, &
15         ibas_con, pmflxr, pmflxs, prfl, psfl, da, phi, mp, upwd, dnwd, &         phi, mp, upwd, dnwd, tr_seri, zmasse)
        tr_seri, zmasse)  
16    
17      ! 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
18    
19      ! Authors : Frédéric Hourdin, Abderrahmane Idelkadi, Marie-Alice      ! Authors: Frédéric Hourdin, Abderrahmane Idelkadi, Marie-Alice
20      ! Foujols, Olivia      ! Foujols, Olivia
21      ! Objet : moniteur général des tendances des traceurs      ! Objet : moniteur général des tendances des traceurs
22    
23      ! Remarques :      ! L'appel de "phytrac" se fait avec "nqmx-2" donc nous avons bien
     ! 1/ L'appel de "phytrac" se fait avec "nq-2" donc nous avons bien  
24      ! les vrais traceurs (en nombre "nbtr", sans la vapeur d'eau ni l'eau      ! les vrais traceurs (en nombre "nbtr", sans la vapeur d'eau ni l'eau
25      ! liquide) dans "phytrac".      ! liquide) dans "phytrac".
     ! 2/ Le choix du radon et du plomb se fait juste avec un "data"  
     ! (peu propre).  
     ! Pourrait-on avoir une variable qui indiquerait le type de traceur ?  
26    
27      use dimens_m, only: llm      use dimens_m, only: llm
28      use indicesol, only: nbsrf      use indicesol, only: nbsrf
# Line 42  contains Line 35  contains
35      use regr_pr_comb_coefoz_m, only: regr_pr_comb_coefoz      use regr_pr_comb_coefoz_m, only: regr_pr_comb_coefoz
36      use phyetat0_m, only: rlat      use phyetat0_m, only: rlat
37      use o3_chem_m, only: o3_chem      use o3_chem_m, only: o3_chem
38      use ini_hist, only: ini_histrac      use ini_histrac_m, only: ini_histrac
39      use radiornpb_m, only: radiornpb      use radiornpb_m, only: radiornpb
40      use minmaxqfi_m, only: minmaxqfi      use minmaxqfi_m, only: minmaxqfi
41      use numer_rec, only: assert      use numer_rec, only: assert
42      use press_coefoz_m, only: press_coefoz      use press_coefoz_m, only: press_coefoz
43    
     ! Arguments:  
   
     !   EN ENTREE:  
   
     !   divers:  
   
44      logical, intent(in):: rnpb      logical, intent(in):: rnpb
45    
46      integer, intent(in):: nqmax      integer, intent(in):: nq_phys
47      ! (nombre de traceurs auxquels on applique la physique)      ! (nombre de traceurs auxquels on applique la physique)
48    
49      integer, intent(in):: itap  ! number of calls to "physiq"      integer, intent(in):: itap  ! number of calls to "physiq"
50      integer, intent(in):: lmt_pas ! number of time steps of "physics" per day      integer, intent(in):: lmt_pas ! number of time steps of "physics" per day
51      integer, intent(in):: julien !jour julien, 1 <= julien <= 360      integer, intent(in):: julien !jour julien, 1 <= julien <= 360
     integer itop_con(klon)  
     integer ibas_con(klon)  
52      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
53      real, intent(in):: pdtphys  ! pas d'integration pour la physique (s)      real, intent(in):: pdtphys  ! pas d'integration pour la physique (s)
54      real, intent(in):: t_seri(klon, llm) ! temperature, in K      real, intent(in):: t_seri(klon, llm) ! temperature, in K
55    
56      real, intent(inout):: tr_seri(klon, llm, nbtr)      real, intent(inout):: tr_seri(:, :, :) ! (klon, llm, nbtr)
57      ! (mass fractions of tracers, excluding water, at mid-layers)      ! (mass fractions of tracers, excluding water, at mid-layers)
58    
59      real u(klon, llm)      real u(klon, llm)
# Line 91  contains Line 76  contains
76    
77      real pphi(klon, llm) ! geopotentiel      real pphi(klon, llm) ! geopotentiel
78      real pphis(klon)      real pphis(klon)
     REAL, intent(in):: presnivs(llm)  
79      logical, intent(in):: firstcal ! first call to "calfis"      logical, intent(in):: firstcal ! first call to "calfis"
80      logical, intent(in):: lafin ! fin de la physique      logical, intent(in):: lafin ! fin de la physique
81    
# Line 211  contains Line 195  contains
195    
196      !--------------------------------------      !--------------------------------------
197    
198      call assert(shape(zmasse) == (/klon, llm/), "phytrac")      call assert(shape(zmasse) == (/klon, llm/), "phytrac zmasse")
199        call assert(shape(tr_seri) == (/klon, llm, nbtr/), "phytrac tr_seri")
200    
201      if (firstcal) then      if (firstcal) then
202         print *, 'phytrac: pdtphys = ', pdtphys         print *, 'phytrac: pdtphys = ', pdtphys
203         PRINT *, 'Fréquence de sortie des traceurs : ecrit_tra = ', ecrit_tra         PRINT *, 'Fréquence de sortie des traceurs : ecrit_tra = ', ecrit_tra
204         if (nbtr < nqmax) call abort_gcm('phytrac', 'See above', 1)         if (nbtr < nq_phys) call abort_gcm('phytrac', 'nbtr < nq_phys', 1)
205         inirnpb=rnpb         inirnpb=rnpb
206    
207         ! Initialisation des sorties :         ! Initialisation des sorties :
208         call ini_histrac(nid_tra, pdtphys, presnivs, nqmax, lessivage)         call ini_histrac(nid_tra, pdtphys, nq_phys, lessivage)
209    
210         ! Initialisation de certaines variables pour le radon et le plomb         ! Initialisation de certaines variables pour le radon et le plomb
211         ! Initialisation du traceur dans le sol (couche limite radonique)         ! Initialisation du traceur dans le sol (couche limite radonique)
# Line 239  contains Line 224  contains
224    
225         ! Initialisation de la nature des traceurs         ! Initialisation de la nature des traceurs
226    
227         DO it = 1, nqmax         DO it = 1, nq_phys
228            aerosol(it) = .FALSE.  ! Tous les traceurs sont des gaz par defaut            aerosol(it) = .FALSE.  ! Tous les traceurs sont des gaz par defaut
229            radio(it) = .FALSE. ! par défaut pas de passage par "radiornpb"            radio(it) = .FALSE. ! par défaut pas de passage par "radiornpb"
230            clsol(it) = .FALSE.  ! Par defaut couche limite avec flux prescrit            clsol(it) = .FALSE.  ! Par defaut couche limite avec flux prescrit
231         ENDDO         ENDDO
232    
233         if (nqmax >= 3) then         if (nq_phys >= 3) then
234            call press_coefoz ! read input pressure levels for ozone coefficients            call press_coefoz ! read input pressure levels for ozone coefficients
235         end if         end if
236      ENDIF      ENDIF
# Line 267  contains Line 252  contains
252      ! Calcul de l'effet de la convection      ! Calcul de l'effet de la convection
253    
254      if (convection) then      if (convection) then
255         DO it=1, nqmax         DO it=1, nq_phys
256            if (iflag_con.eq.2) then            if (iflag_con.eq.2) then
257               ! tiedke               ! tiedke
258               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 276  contains
276    
277      ! Calcul de l'effet des thermiques      ! Calcul de l'effet des thermiques
278    
279      do it=1, nqmax      do it=1, nq_phys
280         do k=1, llm         do k=1, llm
281            do i=1, klon            do i=1, klon
282               d_tr_th(i, k, it)=0.               d_tr_th(i, k, it)=0.
# Line 303  contains Line 288  contains
288    
289      if (iflag_thermals > 0) then      if (iflag_thermals > 0) then
290         nsplit=10         nsplit=10
291         DO it=1, nqmax         DO it=1, nq_phys
292            do isplit=1, nsplit            do isplit=1, nsplit
293               ! Thermiques               ! Thermiques
294               call dqthermcell(klon, llm, pdtphys/nsplit &               call dqthermcell(klon, llm, pdtphys/nsplit &
# Line 332  contains Line 317  contains
317         ENDDO         ENDDO
318    
319         ! MAF modif pour tenir compte du cas rnpb + traceur         ! MAF modif pour tenir compte du cas rnpb + traceur
320         DO it=1, nqmax         DO it=1, nq_phys
321            if (clsol(it)) then            if (clsol(it)) then
322               ! couche limite avec quantite dans le sol calculee               ! couche limite avec quantite dans le sol calculee
323               CALL cltracrn(it, pdtphys, yu1, yv1, &               CALL cltracrn(it, pdtphys, yu1, yv1, &
# Line 380  contains Line 365  contains
365      ! si radio=true mais pour l'instant radiornpb propre au cas rnpb      ! si radio=true mais pour l'instant radiornpb propre au cas rnpb
366      if (rnpb) then      if (rnpb) then
367         d_tr_dec(:, :, :) = radiornpb(tr_seri, pdtphys, tautr)         d_tr_dec(:, :, :) = radiornpb(tr_seri, pdtphys, tautr)
368         DO it=1, nqmax         DO it=1, nq_phys
369            if (radio(it)) then            if (radio(it)) then
370               tr_seri(:, :, it) = tr_seri(:, :, it) + d_tr_dec(:, :, it)               tr_seri(:, :, it) = tr_seri(:, :, it) + d_tr_dec(:, :, it)
371               WRITE(unit=itn, fmt='(i1)') it               WRITE(unit=itn, fmt='(i1)') it
# Line 389  contains Line 374  contains
374         ENDDO         ENDDO
375      endif ! rnpb decroissance  radioactive      endif ! rnpb decroissance  radioactive
376    
377      if (nqmax >= 3) then      if (nq_phys >= 3) then
378         ! Ozone as a tracer:         ! Ozone as a tracer:
379         if (mod(itap - 1, lmt_pas) == 0) then         if (mod(itap - 1, lmt_pas) == 0) then
380            ! Once per day, update the coefficients for ozone chemistry:            ! Once per day, update the coefficients for ozone chemistry:
# Line 407  contains Line 392  contains
392    
393         ! tendance des aerosols nuclees et impactes         ! tendance des aerosols nuclees et impactes
394    
395         DO it = 1, nqmax         DO it = 1, nq_phys
396            IF (aerosol(it)) THEN            IF (aerosol(it)) THEN
397               DO k = 1, llm               DO k = 1, llm
398                  DO i = 1, klon                  DO i = 1, klon
# Line 423  contains Line 408  contains
408         ! Mises a jour des traceurs + calcul des flux de lessivage         ! Mises a jour des traceurs + calcul des flux de lessivage
409         ! Mise a jour due a l'impaction et a la nucleation         ! Mise a jour due a l'impaction et a la nucleation
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 436  contains Line 421  contains
421    
422         ! Flux lessivage total         ! Flux lessivage total
423    
424         DO it = 1, nqmax         DO it = 1, nq_phys
425            DO k = 1, llm            DO k = 1, llm
426               DO i = 1, klon               DO i = 1, klon
427                  flestottr(i, k, it) = flestottr(i, k, it) - &                  flestottr(i, k, it) = flestottr(i, k, it) - &
# Line 450  contains Line 435  contains
435      ENDIF      ENDIF
436    
437      !   Ecriture des sorties      !   Ecriture des sorties
438      call write_histrac(lessivage, nqmax, itap, nid_tra)      call write_histrac(lessivage, nq_phys, itap, nid_tra)
439    
440      if (lafin) then      if (lafin) then
441         print *, "C'est la fin de la physique."         print *, "C'est la fin de la physique."
# Line 464  contains Line 449  contains
449    
450    contains    contains
451    
452      subroutine write_histrac(lessivage, nqmax, itap, nid_tra)      subroutine write_histrac(lessivage, nq_phys, itap, nid_tra)
453    
454        ! 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
455    
456        use dimens_m, only: iim, jjm, llm        use dimens_m, only: iim, jjm, llm
457        use ioipsl, only: histwrite, histsync        use histcom, only: histsync
458          use histwrite_m, only: histwrite
459        use temps, only: itau_phy        use temps, only: itau_phy
460        use advtrac_m, only: tnom        use iniadvtrac_m, only: tnom
461        use comgeomphy, only: airephy        use comgeomphy, only: airephy
462        use dimphy, only: klon        use dimphy, only: klon
463          use grid_change, only: gr_phy_write_2d
464          use gr_phy_write_3d_m, only: gr_phy_write_3d
465    
466        logical, intent(in):: lessivage        logical, intent(in):: lessivage
467    
468        integer, intent(in):: nqmax        integer, intent(in):: nq_phys
469        ! (nombre de traceurs auxquels on applique la physique)        ! (nombre de traceurs auxquels on applique la physique)
470    
471        integer, intent(in):: itap  ! number of calls to "physiq"        integer, intent(in):: itap  ! number of calls to "physiq"
# Line 486  contains Line 474  contains
474        ! Variables local to the procedure:        ! Variables local to the procedure:
475        integer it        integer it
476        integer itau_w   ! pas de temps ecriture        integer itau_w   ! pas de temps ecriture
       REAL zx_tmp_2d(iim, jjm+1), zx_tmp_3d(iim, jjm+1, llm)  
477        logical, parameter:: ok_sync = .true.        logical, parameter:: ok_sync = .true.
478    
479        !-----------------------------------------------------        !-----------------------------------------------------
480    
481        itau_w = itau_phy + itap        itau_w = itau_phy + itap
482    
483        CALL gr_fi_ecrit(1, klon, iim, jjm+1, pphis, zx_tmp_2d)        CALL histwrite(nid_tra, "phis", itau_w, gr_phy_write_2d(pphis))
484        CALL histwrite(nid_tra, "phis", itau_w, zx_tmp_2d)        CALL histwrite(nid_tra, "aire", itau_w, gr_phy_write_2d(airephy))
485          CALL histwrite(nid_tra, "zmasse", itau_w, gr_phy_write_3d(zmasse))
486        CALL gr_fi_ecrit(1, klon, iim, jjm+1, airephy, zx_tmp_2d)        
487        CALL histwrite(nid_tra, "aire", itau_w, zx_tmp_2d)        DO it=1, nq_phys
488             CALL histwrite(nid_tra, tnom(it+2), itau_w, &
489        CALL gr_fi_ecrit(llm, klon, iim, jjm+1, zmasse, zx_tmp_3d)                      gr_phy_write_3d(tr_seri(:, :, it)))
       CALL histwrite(nid_tra, "zmasse", itau_w, zx_tmp_3d)  
   
       DO it=1, nqmax  
          CALL gr_fi_ecrit(llm, klon, iim, jjm+1, tr_seri(1, 1, it), zx_tmp_3d)  
          CALL histwrite(nid_tra, tnom(it+2), itau_w, zx_tmp_3d)  
490           if (lessivage) THEN           if (lessivage) THEN
491              CALL gr_fi_ecrit(llm, klon, iim, jjm+1, flestottr(1, 1, it), &              CALL histwrite(nid_tra, "fl"//tnom(it+2), itau_w, &
492                   zx_tmp_3d)                   gr_phy_write_3d(flestottr(:, :, it)))
             CALL histwrite(nid_tra, "fl"//tnom(it+2), itau_w, zx_tmp_3d)  
493           endif           endif
494             CALL histwrite(nid_tra, "d_tr_th_"//tnom(it+2), itau_w, &
495           CALL gr_fi_ecrit(llm, klon, iim, jjm+1, d_tr_th(1, 1, it), zx_tmp_3d)                gr_phy_write_3d(d_tr_th(:, :, it)))
496           CALL histwrite(nid_tra, "d_tr_th_"//tnom(it+2), itau_w, zx_tmp_3d)           CALL histwrite(nid_tra, "d_tr_cv_"//tnom(it+2), itau_w, &
497           CALL gr_fi_ecrit(llm, klon, iim, jjm+1, d_tr_cv(1, 1, it), zx_tmp_3d)                gr_phy_write_3d(d_tr_cv(:, :, it)))
498           CALL histwrite(nid_tra, "d_tr_cv_"//tnom(it+2), itau_w, zx_tmp_3d)           CALL histwrite(nid_tra, "d_tr_cl_"//tnom(it+2), itau_w, &
499           CALL gr_fi_ecrit(llm, klon, iim, jjm+1, d_tr_cl(1, 1, it), zx_tmp_3d)                gr_phy_write_3d(d_tr_cl(:, :, it)))
          CALL histwrite(nid_tra, "d_tr_cl_"//tnom(it+2), itau_w, zx_tmp_3d)  
500        ENDDO        ENDDO
501    
502        CALL gr_fi_ecrit(llm, klon, iim, jjm+1, pplay, zx_tmp_3d)        CALL histwrite(nid_tra, "pplay", itau_w, gr_phy_write_3d(pplay))
503        CALL histwrite(nid_tra, "pplay", itau_w, zx_tmp_3d)        CALL histwrite(nid_tra, "T", itau_w, gr_phy_write_3d(t_seri))
   
       CALL gr_fi_ecrit(llm, klon, iim, jjm+1, t_seri, zx_tmp_3d)  
       CALL histwrite(nid_tra, "t", itau_w, zx_tmp_3d)  
504    
505        if (ok_sync) then        if (ok_sync) then
506           call histsync(nid_tra)           call histsync(nid_tra)

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

  ViewVC Help
Powered by ViewVC 1.1.21