/[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 15 by guez, Fri Aug 1 15:24:12 2008 UTC revision 17 by guez, Tue Aug 5 13:31:32 2008 UTC
# Line 14  contains Line 14  contains
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, &
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, &
18           tr_seri, zmasse)
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    
# Line 30  contains Line 31  contains
31      ! (peu propre).      ! (peu propre).
32      ! Pourrait-on avoir une variable qui indiquerait le type de traceur ?      ! Pourrait-on avoir une variable qui indiquerait le type de traceur ?
33    
34      use dimens_m, only: iim, jjm, llm      use dimens_m, only: llm
35      use indicesol, only: nbsrf      use indicesol, only: nbsrf
36      use dimphy, only: klon, nbtr      use dimphy, only: klon, nbtr
37      use clesphys, only: ecrit_tra      use clesphys, only: ecrit_tra
# Line 41  contains Line 42  contains
42      use regr_pr_comb_coefoz_m, only: regr_pr_comb_coefoz      use regr_pr_comb_coefoz_m, only: regr_pr_comb_coefoz
43      use phyetat0_m, only: rlat      use phyetat0_m, only: rlat
44      use o3_chem_m, only: o3_chem      use o3_chem_m, only: o3_chem
45        use ini_hist, only: ini_histrac
46        use radiornpb_m, only: radiornpb
47        use minmaxqfi_m, only: minmaxqfi
48        use numer_rec, only: assert
49        use press_coefoz_m, only: press_coefoz
50    
51      ! Arguments:      ! Arguments:
52    
# Line 62  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 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 89  contains Line 95  contains
95      logical, intent(in):: firstcal ! first call to "calfis"      logical, intent(in):: firstcal ! first call to "calfis"
96      logical, intent(in):: lafin ! fin de la physique      logical, intent(in):: lafin ! fin de la physique
97    
     integer nsplit  
98      REAL pmflxr(klon, llm+1), pmflxs(klon, llm+1)   !--lessivage convection      REAL pmflxr(klon, llm+1), pmflxs(klon, llm+1)   !--lessivage convection
99      REAL prfl(klon, llm+1),   psfl(klon, llm+1)     !--lessivage large-scale      REAL prfl(klon, llm+1),   psfl(klon, llm+1)     !--lessivage large-scale
100    
101      !   convection:      !   convection:
   
102      REAL pmfu(klon, llm)  ! flux de masse dans le panache montant      REAL pmfu(klon, llm)  ! flux de masse dans le panache montant
103      REAL pmfd(klon, llm)  ! flux de masse dans le panache descendant      REAL pmfd(klon, llm)  ! flux de masse dans le panache descendant
104      REAL pen_u(klon, llm) ! flux entraine dans le panache montant      REAL pen_u(klon, llm) ! flux entraine dans le panache montant
# Line 129  contains Line 133  contains
133      real ftsol(klon, nbsrf)  ! Temperature du sol (surf)(Kelvin)      real ftsol(klon, nbsrf)  ! Temperature du sol (surf)(Kelvin)
134      real pctsrf(klon, nbsrf) ! Pourcentage de sol f(nature du sol)      real pctsrf(klon, nbsrf) ! Pourcentage de sol f(nature du sol)
135    
136      real pftsol1(klon), pftsol2(klon), pftsol3(klon), pftsol4(klon)      real, intent(in):: zmasse(:, :)  ! (klon, llm)
137      real ppsrf1(klon), ppsrf2(klon), ppsrf3(klon), ppsrf4(klon)      ! (column-density of mass of air in a cell, in kg m-2)
138    
139        ! Variables local to the procedure:
140    
141        integer nsplit
142    
143      !  VARIABLES LOCALES TRACEURS      !  TRACEURS
144    
145      ! Sources et puits des traceurs:      ! Sources et puits des traceurs:
146    
# Line 192  contains Line 200  contains
200      REAL flestottr(klon, llm, nbtr) ! flux de lessivage      REAL flestottr(klon, llm, nbtr) ! flux de lessivage
201      !                                    ! dans chaque couche      !                                    ! dans chaque couche
202    
     real zmasse(klon, llm)  
     ! (column-density of mass of air in a layer, in kg m-2)  
   
203      real ztra_th(klon, llm)      real ztra_th(klon, llm)
   
     character(len=20) modname  
     character(len=80) abort_message  
204      integer isplit      integer isplit
205    
206      ! Controls:      ! Controls:
# Line 209  contains Line 211  contains
211    
212      !--------------------------------------      !--------------------------------------
213    
214      modname='phytrac'      call assert(shape(zmasse) == (/klon, llm/), "phytrac")
215    
216      if (firstcal) then      if (firstcal) then
217         print *, 'phytrac: pdtphys = ', pdtphys         print *, 'phytrac: pdtphys = ', pdtphys
218         PRINT *, 'Fréquence de sortie des traceurs : ecrit_tra = ', ecrit_tra         PRINT *, 'Fréquence de sortie des traceurs : ecrit_tra = ', ecrit_tra
219         if (nbtr < nqmax) then         if (nbtr < nqmax) call abort_gcm('phytrac', 'See above', 1)
           abort_message='See above'  
           call abort_gcm(modname, abort_message, 1)  
        endif  
220         inirnpb=rnpb         inirnpb=rnpb
221    
222         ! Initialisation des sorties :         ! Initialisation des sorties :
# Line 245  contains Line 244  contains
244            radio(it) = .FALSE. ! par défaut pas de passage par "radiornpb"            radio(it) = .FALSE. ! par défaut pas de passage par "radiornpb"
245            clsol(it) = .FALSE.  ! Par defaut couche limite avec flux prescrit            clsol(it) = .FALSE.  ! Par defaut couche limite avec flux prescrit
246         ENDDO         ENDDO
247    
248           if (nqmax >= 3) then
249              call press_coefoz ! read input pressure levels for ozone coefficients
250           end if
251      ENDIF      ENDIF
252    
253      ! Initialisation du traceur dans le sol (couche limite radonique)      ! Initialisation du traceur dans le sol (couche limite radonique)
# Line 261  contains Line 264  contains
264         inirnpb=.false.         inirnpb=.false.
265      endif      endif
266    
     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  
   
267      ! Calcul de l'effet de la convection      ! Calcul de l'effet de la convection
268    
269      if (convection) then      if (convection) then
# Line 299  contains Line 289  contains
289         ENDDO         ENDDO
290      endif      endif
291    
     forall (k=1: llm) zmasse(:, k) = (paprs(:, k)-paprs(:, k+1)) / rg  
   
292      ! Calcul de l'effet des thermiques      ! Calcul de l'effet des thermiques
293    
294      do it=1, nqmax      do it=1, nqmax
# Line 496  contains Line 484  contains
484        integer, intent(in):: nid_tra        integer, intent(in):: nid_tra
485    
486        ! Variables local to the procedure:        ! Variables local to the procedure:
       INTEGER ndex2d(iim*(jjm+1)), ndex3d(iim*(jjm+1)*llm)  
487        integer it        integer it
488        integer itau_w   ! pas de temps ecriture        integer itau_w   ! pas de temps ecriture
489        REAL zx_tmp_2d(iim, jjm+1), zx_tmp_3d(iim, jjm+1, llm)        REAL zx_tmp_2d(iim, jjm+1), zx_tmp_3d(iim, jjm+1, llm)
# Line 504  contains Line 491  contains
491    
492        !-----------------------------------------------------        !-----------------------------------------------------
493    
       ndex2d = 0  
       ndex3d = 0  
494        itau_w = itau_phy + itap        itau_w = itau_phy + itap
495    
496        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)
# Line 548  contains Line 533  contains
533    
534    END SUBROUTINE phytrac    END SUBROUTINE phytrac
535    
   !*************************************************  
   
   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_2d  
     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_2d(rlat)  
     CALL histbeg_totreg("histrac", rlon(2:iim+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, &  
          "once",  zsto, zout)  
     CALL histdef(nid_tra, "aire", "Grid area", "-", &  
          iim, jjm+1, nhori, 1, 1, 1, -99, &  
          "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, "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, "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, &  
                "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, &  
             "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, &  
             "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, &  
             "ave(X)", zsto, zout)  
        !---fin Olivia      
   
     ENDDO  
   
     CALL histdef(nid_tra, "pplay", "", "-", &  
          iim, jjm+1, nhori, llm, 1, llm, nvert, &  
          "inst(X)", zout, zout)  
     CALL histdef(nid_tra, "t", "", "-", &  
          iim, jjm+1, nhori, llm, 1, llm, nvert, &  
          "inst(X)", zout, 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 numer_rec, 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 numer_rec, 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  
   
536  end module phytrac_m  end module phytrac_m

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

  ViewVC Help
Powered by ViewVC 1.1.21