/[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 6 by guez, Tue Mar 4 14:00:42 2008 UTC revision 30 by guez, Thu Apr 1 09:07:28 2010 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, &         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, pphis, pphi, albsol, rh, cldfra, rneb, &
16         pphi, albsol, sh, rh, cldfra, rneb, diafra, cldliq, itop_con, &         diafra, cldliq, itop_con, ibas_con, pmflxr, pmflxs, prfl, psfl, da, &
17         ibas_con, pmflxr, pmflxs, prfl, psfl, da, phi, mp, upwd, dnwd, tr_seri)         phi, mp, upwd, dnwd, tr_seri, zmasse)
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
20    
21      ! Authors : Frédéric Hourdin, Abderrahmane Idelkadi, Marie-Alice      ! Authors: Frédéric Hourdin, Abderrahmane Idelkadi, Marie-Alice
22      ! Foujols, Olivia      ! Foujols, Olivia
23      ! Objet : moniteur général des tendances des traceurs      ! Objet : moniteur général des tendances des traceurs
24    
# Line 30  contains Line 30  contains
30      ! (peu propre).      ! (peu propre).
31      ! Pourrait-on avoir une variable qui indiquerait le type de traceur ?      ! Pourrait-on avoir une variable qui indiquerait le type de traceur ?
32    
33      use dimens_m, only: iim, jjm, llm      use dimens_m, only: 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        use ini_hist, only: ini_histrac
45        use radiornpb_m, only: radiornpb
46        use minmaxqfi_m, only: minmaxqfi
47        use numer_rec, only: assert
48        use press_coefoz_m, only: press_coefoz
49    
50      ! Arguments:      ! Arguments:
51    
# Line 49  contains Line 55  contains
55    
56      logical, intent(in):: rnpb      logical, intent(in):: rnpb
57    
58      integer, intent(in):: nqmax      integer, intent(in):: nq_phys
59      ! (nombre de traceurs auxquels on applique la physique)      ! (nombre de traceurs auxquels on applique la physique)
60    
61      integer, intent(in):: nstep  ! appel physique      integer, intent(in):: itap  ! number of calls to "physiq"
62        integer, intent(in):: lmt_pas ! number of time steps of "physics" per day
63      integer, intent(in):: julien !jour julien, 1 <= julien <= 360      integer, intent(in):: julien !jour julien, 1 <= julien <= 360
64      integer itop_con(klon)      integer itop_con(klon)
65      integer ibas_con(klon)      integer ibas_con(klon)
66      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
67      real pdtphys  ! pas d'integration pour la physique (s)      real, intent(in):: pdtphys  ! pas d'integration pour la physique (s)
68      real, intent(in):: t_seri(klon, llm) ! temperature, in K      real, intent(in):: t_seri(klon, llm) ! temperature, in K
69    
70      real tr_seri(klon, llm, nbtr)      real, intent(inout):: tr_seri(:, :, :) ! (klon, llm, nbtr)
71      ! (mass fractions of tracers, excluding water, at mid-layers)      ! (mass fractions of tracers, excluding water, at mid-layers)
72    
73      real u(klon, llm)      real u(klon, llm)
74      real v(klon, llm)      real v(klon, llm)
     real sh(klon, llm)     ! humidite specifique  
75      real rh(klon, llm)     ! humidite relative      real rh(klon, llm)     ! humidite relative
76      real cldliq(klon, llm) ! eau liquide nuageuse      real cldliq(klon, llm) ! eau liquide nuageuse
77      real cldfra(klon, llm) ! fraction nuageuse (tous les nuages)      real cldfra(klon, llm) ! fraction nuageuse (tous les nuages)
# Line 79  contains Line 85  contains
85      real, intent(in):: paprs(klon, llm+1)      real, intent(in):: paprs(klon, llm+1)
86      ! (pression pour chaque inter-couche, en Pa)      ! (pression pour chaque inter-couche, en Pa)
87    
88      real pplay(klon, llm)  ! pression pour le mileu de chaque couche (en Pa)      real, intent(in):: pplay(klon, llm)
89        ! (pression pour le mileu de chaque couche, en Pa)
90    
91      real pphi(klon, llm) ! geopotentiel      real pphi(klon, llm) ! geopotentiel
92      real pphis(klon)      real pphis(klon)
93      REAL, intent(in):: presnivs(llm)      logical, intent(in):: firstcal ! first call to "calfis"
     logical, intent(in):: debutphy ! le flag de l'initialisation de la physique  
94      logical, intent(in):: lafin ! fin de la physique      logical, intent(in):: lafin ! fin de la physique
95    
     integer nsplit  
96      REAL pmflxr(klon, llm+1), pmflxs(klon, llm+1)   !--lessivage convection      REAL pmflxr(klon, llm+1), pmflxs(klon, llm+1)   !--lessivage convection
97      REAL prfl(klon, llm+1),   psfl(klon, llm+1)     !--lessivage large-scale      REAL prfl(klon, llm+1),   psfl(klon, llm+1)     !--lessivage large-scale
98    
99      !   convection:      !   convection:
   
100      REAL pmfu(klon, llm)  ! flux de masse dans le panache montant      REAL pmfu(klon, llm)  ! flux de masse dans le panache montant
101      REAL pmfd(klon, llm)  ! flux de masse dans le panache descendant      REAL pmfd(klon, llm)  ! flux de masse dans le panache descendant
102      REAL pen_u(klon, llm) ! flux entraine dans le panache montant      REAL pen_u(klon, llm) ! flux entraine dans le panache montant
# Line 126  contains Line 131  contains
131      real ftsol(klon, nbsrf)  ! Temperature du sol (surf)(Kelvin)      real ftsol(klon, nbsrf)  ! Temperature du sol (surf)(Kelvin)
132      real pctsrf(klon, nbsrf) ! Pourcentage de sol f(nature du sol)      real pctsrf(klon, nbsrf) ! Pourcentage de sol f(nature du sol)
133    
134      real pftsol1(klon), pftsol2(klon), pftsol3(klon), pftsol4(klon)      real, intent(in):: zmasse(:, :)  ! (klon, llm)
135      real ppsrf1(klon), ppsrf2(klon), ppsrf3(klon), ppsrf4(klon)      ! (column-density of mass of air in a cell, in kg m-2)
136    
137        ! Variables local to the procedure:
138    
139        integer nsplit
140    
141      !  VARIABLES LOCALES TRACEURS      !  TRACEURS
142    
143      ! Sources et puits des traceurs:      ! Sources et puits des traceurs:
144    
# Line 189  contains Line 198  contains
198      REAL flestottr(klon, llm, nbtr) ! flux de lessivage      REAL flestottr(klon, llm, nbtr) ! flux de lessivage
199      !                                    ! dans chaque couche      !                                    ! dans chaque couche
200    
     real zmasse(klon, llm)  
     ! (column-density of mass of air in a layer, in kg m-2)  
   
201      real ztra_th(klon, llm)      real ztra_th(klon, llm)
   
     character(len=20) modname  
     character(len=80) abort_message  
202      integer isplit      integer isplit
203    
204      ! Controls:      ! Controls:
# Line 206  contains Line 209  contains
209    
210      !--------------------------------------      !--------------------------------------
211    
212      modname='phytrac'      call assert(shape(zmasse) == (/klon, llm/), "phytrac zmasse")
213        call assert(shape(tr_seri) == (/klon, llm, nbtr/), "phytrac tr_seri")
214    
215      if (debutphy) then      if (firstcal) then
216         print *, 'phytrac: pdtphys = ', pdtphys         print *, 'phytrac: pdtphys = ', pdtphys
217         PRINT *, 'Fréquence de sortie des traceurs : ecrit_tra = ', ecrit_tra         PRINT *, 'Fréquence de sortie des traceurs : ecrit_tra = ', ecrit_tra
218         if (nbtr < nqmax) then         if (nbtr < nq_phys) call abort_gcm('phytrac', 'nbtr < nq_phys', 1)
           abort_message='See above'  
           call abort_gcm(modname, abort_message, 1)  
        endif  
219         inirnpb=rnpb         inirnpb=rnpb
220    
221         ! Initialisation des sorties :         ! Initialisation des sorties :
222         call ini_histrac(nid_tra, pdtphys, presnivs, nqmax, lessivage)         call ini_histrac(nid_tra, pdtphys, nq_phys, lessivage)
223    
224         ! Initialisation de certaines variables pour le radon et le plomb         ! Initialisation de certaines variables pour le radon et le plomb
225         ! Initialisation du traceur dans le sol (couche limite radonique)         ! Initialisation du traceur dans le sol (couche limite radonique)
# Line 237  contains Line 238  contains
238    
239         ! Initialisation de la nature des traceurs         ! Initialisation de la nature des traceurs
240    
241         DO it = 1, nqmax         DO it = 1, nq_phys
242            aerosol(it) = .FALSE.  ! Tous les traceurs sont des gaz par defaut            aerosol(it) = .FALSE.  ! Tous les traceurs sont des gaz par defaut
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
246    
247         if (nqmax >= 3) then         if (nq_phys >= 3) then
248            ! Get the parameters for ozone chemistry:            call press_coefoz ! read input pressure levels for ozone coefficients
           call read_coefoz  
249         end if         end if
250      ENDIF      ENDIF
251    
# Line 263  contains Line 263  contains
263         inirnpb=.false.         inirnpb=.false.
264      endif      endif
265    
     do i=1, klon  
        pftsol1(i) = ftsol(i, 1)  
        pftsol2(i) = ftsol(i, 2)  
        pftsol3(i) = ftsol(i, 3)  
        pftsol4(i) = ftsol(i, 4)  
   
        ppsrf1(i) = pctsrf(i, 1)  
        ppsrf2(i) = pctsrf(i, 2)  
        ppsrf3(i) = pctsrf(i, 3)  
        ppsrf4(i) = pctsrf(i, 4)  
   
     enddo  
   
266      ! Calcul de l'effet de la convection      ! Calcul de l'effet de la convection
267    
268      if (convection) then      if (convection) then
269         DO it=1, nqmax         DO it=1, nq_phys
270            if (iflag_con.eq.2) then            if (iflag_con.eq.2) then
271               ! tiedke               ! tiedke
272               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, &
273                    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))
274            else if (iflag_con.eq.3) then            else if (iflag_con.eq.3) then
275               ! KE               ! KE
276               call cvltr(pdtphys, da, phi, mp, paprs, pplay, &               call cvltr(pdtphys, da, phi, mp, paprs, &
277                    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))
278            endif            endif
279    
# Line 301  contains Line 288  contains
288         ENDDO         ENDDO
289      endif      endif
290    
     forall (k=1: llm) zmasse(:, k) = (paprs(:, k)-paprs(:, k+1)) / rg  
   
291      ! Calcul de l'effet des thermiques      ! Calcul de l'effet des thermiques
292    
293      do it=1, nqmax      do it=1, nq_phys
294         do k=1, llm         do k=1, llm
295            do i=1, klon            do i=1, klon
296               d_tr_th(i, k, it)=0.               d_tr_th(i, k, it)=0.
# Line 317  contains Line 302  contains
302    
303      if (iflag_thermals > 0) then      if (iflag_thermals > 0) then
304         nsplit=10         nsplit=10
305         DO it=1, nqmax         DO it=1, nq_phys
306            do isplit=1, nsplit            do isplit=1, nsplit
307               ! Thermiques               ! Thermiques
308               call dqthermcell(klon, llm, pdtphys/nsplit &               call dqthermcell(klon, llm, pdtphys/nsplit &
# Line 346  contains Line 331  contains
331         ENDDO         ENDDO
332    
333         ! MAF modif pour tenir compte du cas rnpb + traceur         ! MAF modif pour tenir compte du cas rnpb + traceur
334         DO it=1, nqmax         DO it=1, nq_phys
335            if (clsol(it)) then            if (clsol(it)) then
336               ! couche limite avec quantite dans le sol calculee               ! couche limite avec quantite dans le sol calculee
337               CALL cltracrn(it, pdtphys, yu1, yv1, &               CALL cltracrn(it, pdtphys, yu1, yv1, &
# Line 394  contains Line 379  contains
379      ! si radio=true mais pour l'instant radiornpb propre au cas rnpb      ! si radio=true mais pour l'instant radiornpb propre au cas rnpb
380      if (rnpb) then      if (rnpb) then
381         d_tr_dec(:, :, :) = radiornpb(tr_seri, pdtphys, tautr)         d_tr_dec(:, :, :) = radiornpb(tr_seri, pdtphys, tautr)
382         DO it=1, nqmax         DO it=1, nq_phys
383            if (radio(it)) then            if (radio(it)) then
384               tr_seri(:, :, it) = tr_seri(:, :, it) + d_tr_dec(:, :, it)               tr_seri(:, :, it) = tr_seri(:, :, it) + d_tr_dec(:, :, it)
385               WRITE(unit=itn, fmt='(i1)') it               WRITE(unit=itn, fmt='(i1)') it
# Line 403  contains Line 388  contains
388         ENDDO         ENDDO
389      endif ! rnpb decroissance  radioactive      endif ! rnpb decroissance  radioactive
390    
391      if (nqmax >= 3) then      if (nq_phys >= 3) then
392         ! Ozone as a tracer:         ! Ozone as a tracer:
393           if (mod(itap - 1, lmt_pas) == 0) then
394              ! Once per day, update the coefficients for ozone chemistry:
395              call regr_pr_comb_coefoz(julien)
396           end if
397         call o3_chem(julien, gmtime, t_seri, zmasse, pdtphys, tr_seri(:, :, 3))         call o3_chem(julien, gmtime, t_seri, zmasse, pdtphys, tr_seri(:, :, 3))
398      end if      end if
399    
# Line 417  contains Line 406  contains
406    
407         ! tendance des aerosols nuclees et impactes         ! tendance des aerosols nuclees et impactes
408    
409         DO it = 1, nqmax         DO it = 1, nq_phys
410            IF (aerosol(it)) THEN            IF (aerosol(it)) THEN
411               DO k = 1, llm               DO k = 1, llm
412                  DO i = 1, klon                  DO i = 1, klon
# Line 433  contains Line 422  contains
422         ! Mises a jour des traceurs + calcul des flux de lessivage         ! Mises a jour des traceurs + calcul des flux de lessivage
423         ! Mise a jour due a l'impaction et a la nucleation         ! Mise a jour due a l'impaction et a la nucleation
424    
425         DO it = 1, nqmax         DO it = 1, nq_phys
426            IF (aerosol(it)) THEN            IF (aerosol(it)) THEN
427               DO k = 1, llm               DO k = 1, llm
428                  DO i = 1, klon                  DO i = 1, klon
# Line 446  contains Line 435  contains
435    
436         ! Flux lessivage total         ! Flux lessivage total
437    
438         DO it = 1, nqmax         DO it = 1, nq_phys
439            DO k = 1, llm            DO k = 1, llm
440               DO i = 1, klon               DO i = 1, klon
441                  flestottr(i, k, it) = flestottr(i, k, it) - &                  flestottr(i, k, it) = flestottr(i, k, it) - &
# Line 460  contains Line 449  contains
449      ENDIF      ENDIF
450    
451      !   Ecriture des sorties      !   Ecriture des sorties
452      call write_histrac(lessivage, nqmax, nstep, nid_tra)      call write_histrac(lessivage, nq_phys, itap, nid_tra)
453    
454      if (lafin) then      if (lafin) then
455         print *, "C'est la fin de la physique."         print *, "C'est la fin de la physique."
# Line 474  contains Line 463  contains
463    
464    contains    contains
465    
466      subroutine write_histrac(lessivage, nqmax, nstep, nid_tra)      subroutine write_histrac(lessivage, nq_phys, itap, nid_tra)
467    
468        ! 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
469    
470        use dimens_m, only: iim, jjm, llm        use dimens_m, only: iim, jjm, llm
471        use ioipsl, only: histwrite, histsync        use histcom, only: histsync
472          use histwrite_m, only: histwrite
473        use temps, only: itau_phy        use temps, only: itau_phy
474        use advtrac_m, only: tnom        use iniadvtrac_m, only: tnom
475        use comgeomphy, only: airephy        use comgeomphy, only: airephy
476        use dimphy, only: klon        use dimphy, only: klon
477          use grid_change, only: gr_phy_write_2d, gr_phy_write_3d
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):: nstep  ! appel physique        integer, intent(in):: itap  ! number of calls to "physiq"
485        integer, intent(in):: nid_tra        integer, intent(in):: nid_tra
486    
487        ! Variables local to the procedure:        ! Variables local to the procedure:
       INTEGER ndex2d(iim*(jjm+1)), ndex3d(iim*(jjm+1)*llm)  
488        integer it        integer it
489        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)  
490        logical, parameter:: ok_sync = .true.        logical, parameter:: ok_sync = .true.
491    
492        !-----------------------------------------------------        !-----------------------------------------------------
493    
494        ndex2d = 0        itau_w = itau_phy + itap
495        ndex3d = 0  
496        itau_w = itau_phy + nstep        CALL histwrite(nid_tra, "phis", itau_w, gr_phy_write_2d(pphis))
497          CALL histwrite(nid_tra, "aire", itau_w, gr_phy_write_2d(airephy))
498        CALL gr_fi_ecrit(1, klon, iim, jjm+1, pphis, zx_tmp_2d)        CALL histwrite(nid_tra, "zmasse", itau_w, gr_phy_write_3d(zmasse))
499        CALL histwrite(nid_tra, "phis", itau_w, zx_tmp_2d, iim*(jjm+1), ndex2d)  
500          DO it=1, nq_phys
501        CALL gr_fi_ecrit(1, klon, iim, jjm+1, airephy, zx_tmp_2d)                 CALL histwrite(nid_tra, tnom(it+2), itau_w, &
502        CALL histwrite(nid_tra, "aire", itau_w, zx_tmp_2d, iim*(jjm+1), ndex2d)                gr_phy_write_3d(tr_seri(:, :, it)))
   
       CALL gr_fi_ecrit(llm, klon, iim, jjm+1, zmasse, zx_tmp_3d)        
       CALL histwrite(nid_tra, "zmasse", itau_w, zx_tmp_3d, iim*(jjm+1)*llm, &  
            ndex3d)  
   
       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, &  
               iim*(jjm+1)*llm, ndex3d)  
503           if (lessivage) THEN           if (lessivage) THEN
504              CALL gr_fi_ecrit(llm, klon, iim, jjm+1, flestottr(1, 1, it), &              CALL histwrite(nid_tra, "fl"//tnom(it+2), itau_w, &
505                   zx_tmp_3d)                   gr_phy_write_3d(flestottr(:, :, it)))
             CALL histwrite(nid_tra, "fl"//tnom(it+2), itau_w, zx_tmp_3d, &  
                  iim*(jjm+1)*llm, ndex3d)  
506           endif           endif
507             CALL histwrite(nid_tra, "d_tr_th_"//tnom(it+2), itau_w, &
508           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)))
509           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, &
510                iim*(jjm+1)*llm, ndex3d)                gr_phy_write_3d(d_tr_cv(:, :, it)))
511           CALL gr_fi_ecrit(llm, klon, iim, jjm+1, d_tr_cv(1, 1, it), zx_tmp_3d)           CALL histwrite(nid_tra, "d_tr_cl_"//tnom(it+2), itau_w, &
512           CALL histwrite(nid_tra, "d_tr_cv_"//tnom(it+2), itau_w, zx_tmp_3d, &                gr_phy_write_3d(d_tr_cl(:, :, it)))
               iim*(jjm+1)*llm, ndex3d)  
          CALL gr_fi_ecrit(llm, klon, iim, jjm+1, d_tr_cl(1, 1, it), zx_tmp_3d)  
          CALL histwrite(nid_tra, "d_tr_cl_"//tnom(it+2), itau_w, zx_tmp_3d, &  
               iim*(jjm+1)*llm, ndex3d)  
513        ENDDO        ENDDO
514    
515        CALL gr_fi_ecrit(1, klon, iim, jjm+1, yu1, zx_tmp_2d)        CALL histwrite(nid_tra, "pplay", itau_w, gr_phy_write_3d(pplay))
516        CALL histwrite(nid_tra, "pyu1", itau_w, zx_tmp_2d, &        CALL histwrite(nid_tra, "T", itau_w, gr_phy_write_3d(t_seri))
            iim*(jjm+1), ndex2d)  
   
       CALL gr_fi_ecrit(1, klon, iim, jjm+1, yv1, zx_tmp_2d)  
       CALL histwrite(nid_tra, "pyv1", itau_w, zx_tmp_2d, &  
            iim*(jjm+1), ndex2d)  
   
       CALL gr_fi_ecrit(1, klon, iim, jjm+1, pftsol1, zx_tmp_2d)  
       CALL histwrite(nid_tra, "ftsol1", itau_w, zx_tmp_2d, &  
            iim*(jjm+1), ndex2d)  
   
       CALL gr_fi_ecrit(1, klon, iim, jjm+1, pftsol2, zx_tmp_2d)  
       CALL histwrite(nid_tra, "ftsol2", itau_w, zx_tmp_2d, &  
            iim*(jjm+1), ndex2d)  
   
       CALL gr_fi_ecrit(1, klon, iim, jjm+1, pftsol3, zx_tmp_2d)  
       CALL histwrite(nid_tra, "ftsol3", itau_w, zx_tmp_2d, &  
            iim*(jjm+1), ndex2d)  
   
       CALL gr_fi_ecrit(1, klon, iim, jjm+1, pftsol4, zx_tmp_2d)  
       CALL histwrite(nid_tra, "ftsol4", itau_w, zx_tmp_2d, &  
            iim*(jjm+1), ndex2d)  
   
       CALL gr_fi_ecrit(1, klon, iim, jjm+1, ppsrf1, zx_tmp_2d)  
       CALL histwrite(nid_tra, "psrf1", itau_w, zx_tmp_2d, &  
            iim*(jjm+1), ndex2d)  
   
       CALL gr_fi_ecrit(1, klon, iim, jjm+1, ppsrf2, zx_tmp_2d)  
       CALL histwrite(nid_tra, "psrf2", itau_w, zx_tmp_2d, &  
            iim*(jjm+1), ndex2d)  
   
       CALL gr_fi_ecrit(1, klon, iim, jjm+1, ppsrf3, zx_tmp_2d)  
       CALL histwrite(nid_tra, "psrf3", itau_w, zx_tmp_2d, &  
            iim*(jjm+1), ndex2d)  
   
       CALL gr_fi_ecrit(1, klon, iim, jjm+1, ppsrf4, zx_tmp_2d)  
       CALL histwrite(nid_tra, "psrf4", itau_w, zx_tmp_2d, &  
            iim*(jjm+1), ndex2d)  
       CALL gr_fi_ecrit(llm, klon, iim, jjm+1, pplay, zx_tmp_3d)  
       CALL histwrite(nid_tra, "pplay", itau_w, zx_tmp_3d, &  
            iim*(jjm+1)*llm, ndex3d)  
   
       CALL gr_fi_ecrit(llm, klon, iim, jjm+1, t_seri, zx_tmp_3d)  
       CALL histwrite(nid_tra, "t", itau_w, zx_tmp_3d, &  
            iim*(jjm+1)*llm, ndex3d)  
       CALL gr_fi_ecrit(llm, klon, iim, jjm+1, pmfu, zx_tmp_3d)  
       CALL histwrite(nid_tra, "mfu", itau_w, zx_tmp_3d, &  
            iim*(jjm+1)*llm, ndex3d)  
       CALL gr_fi_ecrit(llm, klon, iim, jjm+1, pmfd, zx_tmp_3d)  
       CALL histwrite(nid_tra, "mfd", itau_w, zx_tmp_3d, &  
            iim*(jjm+1)*llm, ndex3d)  
       CALL gr_fi_ecrit(llm, klon, iim, jjm+1, pen_u, zx_tmp_3d)  
       CALL histwrite(nid_tra, "en_u", itau_w, zx_tmp_3d, &  
            iim*(jjm+1)*llm, ndex3d)  
       CALL gr_fi_ecrit(llm, klon, iim, jjm+1, pen_d, zx_tmp_3d)  
       CALL histwrite(nid_tra, "en_d", itau_w, zx_tmp_3d, &  
            iim*(jjm+1)*llm, ndex3d)  
       CALL gr_fi_ecrit(llm, klon, iim, jjm+1, pde_d, zx_tmp_3d)  
       CALL histwrite(nid_tra, "de_d", itau_w, zx_tmp_3d, &  
            iim*(jjm+1)*llm, ndex3d)  
       CALL gr_fi_ecrit(llm, klon, iim, jjm+1, pde_u, zx_tmp_3d)  
       CALL histwrite(nid_tra, "de_u", itau_w, zx_tmp_3d, &  
            iim*(jjm+1)*llm, ndex3d)  
       CALL gr_fi_ecrit(llm, klon, iim, jjm+1, coefh, zx_tmp_3d)  
       CALL histwrite(nid_tra, "coefh", itau_w, zx_tmp_3d, &  
            iim*(jjm+1)*llm, ndex3d)  
   
       ! abder  
517    
518        if (ok_sync) then        if (ok_sync) then
519           call histsync(nid_tra)           call histsync(nid_tra)
# Line 616  contains Line 523  contains
523    
524    END SUBROUTINE phytrac    END SUBROUTINE phytrac
525    
   !*************************************************  
   
   subroutine ini_histrac(nid_tra, pdtphys, presnivs, nqmax, lessivage)  
   
     ! From phylmd/ini_histrac.h, version 1.10 2006/02/21 08:08:30  
   
     use dimens_m, only: iim, jjm, llm  
     use ioipsl, only: ymds2ju, histbeg_totreg, histvert, histdef, histend  
     use temps, only: annee_ref, day_ref, itau_phy  
     use advtrac_m, only: niadv, tnom, ttext  
     use dimphy, only: klon  
     use clesphys, only: ecrit_tra  
     use grid_change, only: gr_phy_write  
     use phyetat0_m, only: rlon, rlat  
   
     INTEGER, intent(out):: nid_tra  
     real, intent(in):: pdtphys  ! pas d'integration pour la physique (s)  
     REAL, intent(in):: presnivs(:)  
   
     integer, intent(in):: nqmax  
     ! (nombre de traceurs auxquels on applique la physique)  
   
     logical, intent(in):: lessivage  
   
     ! Variables local to the procedure:  
   
     REAL zjulian  
     REAL zx_lat(iim, jjm+1)  
     INTEGER nhori, nvert  
     REAL zsto, zout  
     integer it, iq, iiq  
   
     !---------------------------------------------------------  
   
     CALL ymds2ju(annee_ref, month=1, day=day_ref, sec=0.0, julian=zjulian)  
     zx_lat(:, :) = gr_phy_write(rlat)  
     CALL histbeg_totreg("histrac", iim, rlon(2:iim+1), jjm+1, zx_lat(1, :), &  
          1, iim, 1, jjm+1, itau_phy, zjulian, pdtphys, nhori, nid_tra)  
     CALL histvert(nid_tra, "presnivs", "Vertical levels", "mb", llm, &  
          presnivs, nvert)  
   
     zsto = pdtphys  
     zout = pdtphys * REAL(ecrit_tra)  
   
     CALL histdef(nid_tra, "phis", "Surface geop. height", "-", &  
          iim, jjm+1, nhori, 1, 1, 1, -99, 32, &  
          "once",  zsto, zout)  
     CALL histdef(nid_tra, "aire", "Grid area", "-", &  
          iim, jjm+1, nhori, 1, 1, 1, -99, 32, &  
          "once",  zsto, zout)  
     CALL histdef(nid_tra, "zmasse", "column density of air in cell", &  
          "kg m-2", iim, jjm + 1, nhori, llm, 1, llm, nvert, 32, "ave(X)", &  
          zsto, zout)  
   
     DO it=1, nqmax  
        ! champ 2D  
        iq=it+2  
        iiq=niadv(iq)  
        CALL histdef(nid_tra, tnom(iq), ttext(iiq), "U/kga", iim, jjm+1, &  
             nhori, llm, 1, llm, nvert, 32, "ave(X)", zsto, zout)  
        if (lessivage) THEN  
           CALL histdef(nid_tra, "fl"//tnom(iq), "Flux "//ttext(iiq), &  
                "U/m2/s", iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &  
                "ave(X)", zsto, zout)  
        endif  
   
        !---Ajout Olivia  
        CALL histdef(nid_tra, "d_tr_th_"//tnom(iq), &  
             "tendance thermique"// ttext(iiq), "?", &  
             iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &  
             "ave(X)", zsto, zout)  
        CALL histdef(nid_tra, "d_tr_cv_"//tnom(iq), &  
             "tendance convection"// ttext(iiq), "?", &  
             iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &  
             "ave(X)", zsto, zout)  
        CALL histdef(nid_tra, "d_tr_cl_"//tnom(iq), &  
             "tendance couche limite"// ttext(iiq), "?", &  
             iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &  
             "ave(X)", zsto, zout)  
        !---fin Olivia      
   
     ENDDO  
   
     CALL histdef(nid_tra, "pyu1", "Vent niv 1", "-", &  
          iim, jjm+1, nhori, 1, 1, 1, -99, 32, &  
          "inst(X)", zout, zout)  
   
     CALL histdef(nid_tra, "pyv1", "Vent niv 1", "-", &  
          iim, jjm+1, nhori, 1, 1, 1, -99, 32, &  
          "inst(X)",  zout, zout)  
     CALL histdef(nid_tra, "psrf1", "nature sol", "-", &  
          iim, jjm+1, nhori, 1, 1, 1, -99, 32, &  
          "inst(X)",  zout, zout)  
     CALL histdef(nid_tra, "psrf2", "nature sol", "-", &  
          iim, jjm+1, nhori, 1, 1, 1, -99, 32, &  
          "inst(X)",  zout, zout)  
     CALL histdef(nid_tra, "psrf3", "nature sol", "-", &  
          iim, jjm+1, nhori, 1, 1, 1, -99, 32, &  
          "inst(X)",  zout, zout)  
     CALL histdef(nid_tra, "psrf4", "nature sol", "-", &  
          iim, jjm+1, nhori, 1, 1, 1, -99, 32, &  
          "inst(X)",  zout, zout)  
     CALL histdef(nid_tra, "ftsol1", "temper sol", "-", &  
          iim, jjm+1, nhori, 1, 1, 1, -99, 32, &  
          "inst(X)",  zout, zout)  
     CALL histdef(nid_tra, "ftsol2", "temper sol", "-", &  
          iim, jjm+1, nhori, 1, 1, 1, -99, 32, &  
          "inst(X)",  zout, zout)  
     CALL histdef(nid_tra, "ftsol3", "temper sol", "-", &  
          iim, jjm+1, nhori, 1, 1, 1, -99, 32, &  
          "inst(X)",  zout, zout)  
     CALL histdef(nid_tra, "ftsol4", "temper sol", "-", &  
          iim, jjm+1, nhori, 1, 1, 1, -99, 32, &  
          "inst(X)",  zout, zout)  
     CALL histdef(nid_tra, "pplay", "flux u mont", "-", &  
          iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &  
          "inst(X)", zout, zout)  
     CALL histdef(nid_tra, "t", "flux u mont", "-", &  
          iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &  
          "inst(X)", zout, zout)  
     CALL histdef(nid_tra, "mfu", "flux u mont", "-", &  
          iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &  
          "ave(X)", zsto, zout)  
     CALL histdef(nid_tra, "mfd", "flux u decen", "-", &  
          iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &  
          "ave(X)", zsto, zout)  
     CALL histdef(nid_tra, "en_u", "flux u mont", "-", &  
          iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &  
          "ave(X)", zsto, zout)  
     CALL histdef(nid_tra, "en_d", "flux u mont", "-", &  
          iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &  
          "ave(X)", zsto, zout)  
     CALL histdef(nid_tra, "de_d", "flux u mont", "-", &  
          iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &  
          "ave(X)", zsto, zout)  
     CALL histdef(nid_tra, "de_u", "flux u decen", "-", &  
          iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &  
          "ave(X)", zsto, zout)  
     CALL histdef(nid_tra, "coefh", "turbulent coef", "-", &  
          iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &  
          "ave(X)", zsto, zout)  
   
     CALL histend(nid_tra)  
   
   end subroutine ini_histrac  
   
   !*************************************************  
   
   function radiornpb(tr_seri, pdtphys, tautr)  
   
     ! From phylmd/radiornpb.F, v 1.2 2005/05/25 13:10:09  
   
     ! Auteurs: AA + CG (LGGE/CNRS) Date 24-06-94  
     ! Objet: Decroissance radioactive d'un traceur dans l'atmosphere  
     !G 24 06 94 : Pour un traceur, le radon  
     !G 16 12 94 : Plus un 2eme traceur, le 210Pb. Le radon decroit en plomb.  
   
     ! Le pas de temps "pdtphys" est supposé beaucoup plus petit que la  
     ! constante de temps de décroissance.  
   
     use dimens_m, only: llm  
     use dimphy, only: klon, nbtr  
     use nrutil, only: assert  
   
     IMPLICIT none  
   
     REAL, intent(in):: tr_seri(:, :, :), pdtphys, tautr(:)  
     real radiornpb(klon, llm, 2)  
   
     ! Variable local to the procedure:  
     INTEGER it  
   
     !-----------------------------------------------  
   
     call assert(shape(tr_seri) == (/klon, llm, nbtr/), "radiornpb tr_seri")  
     call assert(size(tautr) == nbtr, "radiornpb tautr")  
   
     DO it = 1, 2  
        IF (tautr(it) > 0.) THEN  
           radiornpb(:, :, it) = - tr_seri(:, :, it) * pdtphys / tautr(it)  
        ELSE  
           radiornpb(:, :, it) = 0.  
        END IF  
     END DO  
   
     !G161294 : Cas particulier radon 1 => plomb 2  
     radiornpb(:, :, 2) = radiornpb(:, :, 2) - radiornpb(:, :, 1)  
   
   END function radiornpb  
   
   !*************************************************  
   
   SUBROUTINE minmaxqfi(zq, qmin, qmax, comment)  
   
     ! From phylmd/minmaxqfi.F, version 1.1.1.1 2004/05/19 12:53:09  
   
     use dimens_m, only: llm  
     use dimphy, only: klon  
     use nrutil, only: assert  
   
     IMPLICIT none  
   
     real, intent(in):: zq(:, :), qmin, qmax  
     CHARACTER(len=*), intent(in):: comment  
   
     ! Variables local to the procedure:  
   
     INTEGER jadrs(klon), jbad, k, i  
   
     !---------------------------------  
   
     call assert(shape(zq) == (/klon, llm/), "minmaxqfi")  
   
     DO k = 1, llm  
        jbad = 0  
        DO i = 1, klon  
           IF (zq(i, k) > qmax .OR. zq(i, k) < qmin) THEN  
              jbad = jbad + 1  
              jadrs(jbad) = i  
           ENDIF  
        ENDDO  
        IF (jbad > 0) THEN  
           PRINT *, comment  
           DO i = 1, jbad  
              PRINT *, "zq(", jadrs(i), ", ", k, ") = ", zq(jadrs(i), k)  
           ENDDO  
        ENDIF  
     ENDDO  
   
   end SUBROUTINE minmaxqfi  
   
526  end module phytrac_m  end module phytrac_m

Legend:
Removed from v.6  
changed lines
  Added in v.30

  ViewVC Help
Powered by ViewVC 1.1.21