/[lmdze]/trunk/libf/phylmd/phytrac.f90
ViewVC logotype

Diff of /trunk/libf/phylmd/phytrac.f90

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

revision 3 by guez, Wed Feb 27 13:16:39 2008 UTC revision 15 by guez, Fri Aug 1 15:24:12 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, 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, tr_seri)
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
# Line 33  contains Line 33  contains
33      use dimens_m, only: iim, jjm, llm      use dimens_m, only: iim, jjm, 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    
# Line 52  contains Line 53  contains
53      integer, intent(in):: nqmax      integer, intent(in):: nqmax
54      ! (nombre de traceurs auxquels on applique la physique)      ! (nombre de traceurs auxquels on applique la physique)
55    
56      integer, intent(in):: nstep  ! appel physique      integer, intent(in):: itap  ! number of calls to "physiq"
57        integer, intent(in):: lmt_pas ! number of time steps of "physics" per day
58      integer, intent(in):: julien !jour julien, 1 <= julien <= 360      integer, intent(in):: julien !jour julien, 1 <= julien <= 360
59      integer itop_con(klon)      integer itop_con(klon)
60      integer ibas_con(klon)      integer ibas_con(klon)
61      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
62      real pdtphys  ! pas d'integration pour la physique (s)      real, intent(in):: pdtphys  ! pas d'integration pour la physique (s)
63      real, intent(in):: t_seri(klon, llm) ! temperature, in K      real, intent(in):: t_seri(klon, llm) ! temperature, in K
64    
65      real tr_seri(klon, llm, nbtr)      real tr_seri(klon, llm, nbtr)
# Line 65  contains Line 67  contains
67    
68      real u(klon, llm)      real u(klon, llm)
69      real v(klon, llm)      real v(klon, llm)
     real sh(klon, llm)     ! humidite specifique  
70      real rh(klon, llm)     ! humidite relative      real rh(klon, llm)     ! humidite relative
71      real cldliq(klon, llm) ! eau liquide nuageuse      real cldliq(klon, llm) ! eau liquide nuageuse
72      real cldfra(klon, llm) ! fraction nuageuse (tous les nuages)      real cldfra(klon, llm) ! fraction nuageuse (tous les nuages)
# Line 79  contains Line 80  contains
80      real, intent(in):: paprs(klon, llm+1)      real, intent(in):: paprs(klon, llm+1)
81      ! (pression pour chaque inter-couche, en Pa)      ! (pression pour chaque inter-couche, en Pa)
82    
83      real pplay(klon, llm)  ! pression pour le mileu de chaque couche (en Pa)      real, intent(in):: pplay(klon, llm)
84        ! (pression pour le mileu de chaque couche, en Pa)
85    
86      real pphi(klon, llm) ! geopotentiel      real pphi(klon, llm) ! geopotentiel
87      real pphis(klon)      real pphis(klon)
88      REAL, intent(in):: presnivs(llm)      REAL, intent(in):: presnivs(llm)
89      logical, intent(in):: debutphy ! le flag de l'initialisation de la physique      logical, intent(in):: firstcal ! first call to "calfis"
90      logical, intent(in):: lafin ! fin de la physique      logical, intent(in):: lafin ! fin de la physique
91    
92      integer nsplit      integer nsplit
# Line 208  contains Line 211  contains
211    
212      modname='phytrac'      modname='phytrac'
213    
214      if (debutphy) then      if (firstcal) then
215         print *, 'phytrac: pdtphys = ', pdtphys         print *, 'phytrac: pdtphys = ', pdtphys
216         PRINT *, 'Fréquence de sortie des traceurs : ecrit_tra = ', ecrit_tra         PRINT *, 'Fréquence de sortie des traceurs : ecrit_tra = ', ecrit_tra
217         if (nbtr < nqmax) then         if (nbtr < nqmax) then
# Line 242  contains Line 245  contains
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
   
        ! Get the parameters for ozone chemistry:  
        call read_coefoz  
248      ENDIF      ENDIF
249    
250      ! Initialisation du traceur dans le sol (couche limite radonique)      ! Initialisation du traceur dans le sol (couche limite radonique)
# Line 281  contains Line 281  contains
281            if (iflag_con.eq.2) then            if (iflag_con.eq.2) then
282               ! tiedke               ! tiedke
283               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, &
284                    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))
285            else if (iflag_con.eq.3) then            else if (iflag_con.eq.3) then
286               ! KE               ! KE
287               call cvltr(pdtphys, da, phi, mp, paprs, pplay, &               call cvltr(pdtphys, da, phi, mp, paprs, &
288                    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))
289            endif            endif
290    
# Line 401  contains Line 401  contains
401         ENDDO         ENDDO
402      endif ! rnpb decroissance  radioactive      endif ! rnpb decroissance  radioactive
403    
404      ! Ozone as a tracer:      if (nqmax >= 3) then
405      call o3_chem(julien, gmtime, t_seri, zmasse, pdtphys, tr_seri(:, :, 3))         ! Ozone as a tracer:
406           if (mod(itap - 1, lmt_pas) == 0) then
407              ! Once per day, update the coefficients for ozone chemistry:
408              call regr_pr_comb_coefoz(julien)
409           end if
410           call o3_chem(julien, gmtime, t_seri, zmasse, pdtphys, tr_seri(:, :, 3))
411        end if
412    
413      ! Calcul de l'effet de la precipitation      ! Calcul de l'effet de la precipitation
414    
# Line 456  contains Line 462  contains
462      ENDIF      ENDIF
463    
464      !   Ecriture des sorties      !   Ecriture des sorties
465      call write_histrac(lessivage, nqmax, nstep, nid_tra)      call write_histrac(lessivage, nqmax, itap, nid_tra)
466    
467      if (lafin) then      if (lafin) then
468         print *, "C'est la fin de la physique."         print *, "C'est la fin de la physique."
# Line 470  contains Line 476  contains
476    
477    contains    contains
478    
479      subroutine write_histrac(lessivage, nqmax, nstep, nid_tra)      subroutine write_histrac(lessivage, nqmax, itap, nid_tra)
480    
481        ! 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
482    
# Line 486  contains Line 492  contains
492        integer, intent(in):: nqmax        integer, intent(in):: nqmax
493        ! (nombre de traceurs auxquels on applique la physique)        ! (nombre de traceurs auxquels on applique la physique)
494    
495        integer, intent(in):: nstep  ! appel physique        integer, intent(in):: itap  ! number of calls to "physiq"
496        integer, intent(in):: nid_tra        integer, intent(in):: nid_tra
497    
498        ! Variables local to the procedure:        ! Variables local to the procedure:
# Line 500  contains Line 506  contains
506    
507        ndex2d = 0        ndex2d = 0
508        ndex3d = 0        ndex3d = 0
509        itau_w = itau_phy + nstep        itau_w = itau_phy + itap
510    
511        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)
512        CALL histwrite(nid_tra, "phis", itau_w, zx_tmp_2d, iim*(jjm+1), ndex2d)        CALL histwrite(nid_tra, "phis", itau_w, zx_tmp_2d)
513    
514        CALL gr_fi_ecrit(1, klon, iim, jjm+1, airephy, zx_tmp_2d)              CALL gr_fi_ecrit(1, klon, iim, jjm+1, airephy, zx_tmp_2d)      
515        CALL histwrite(nid_tra, "aire", itau_w, zx_tmp_2d, iim*(jjm+1), ndex2d)        CALL histwrite(nid_tra, "aire", itau_w, zx_tmp_2d)
516    
517        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)      
518        CALL histwrite(nid_tra, "zmasse", itau_w, zx_tmp_3d, iim*(jjm+1)*llm, &        CALL histwrite(nid_tra, "zmasse", itau_w, zx_tmp_3d)
            ndex3d)  
519    
520        DO it=1, nqmax        DO it=1, nqmax
521           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)
522           CALL histwrite(nid_tra, tnom(it+2), itau_w, zx_tmp_3d, &           CALL histwrite(nid_tra, tnom(it+2), itau_w, zx_tmp_3d)
               iim*(jjm+1)*llm, ndex3d)  
523           if (lessivage) THEN           if (lessivage) THEN
524              CALL gr_fi_ecrit(llm, klon, iim, jjm+1, flestottr(1, 1, it), &              CALL gr_fi_ecrit(llm, klon, iim, jjm+1, flestottr(1, 1, it), &
525                   zx_tmp_3d)                   zx_tmp_3d)
526              CALL histwrite(nid_tra, "fl"//tnom(it+2), itau_w, zx_tmp_3d, &              CALL histwrite(nid_tra, "fl"//tnom(it+2), itau_w, zx_tmp_3d)
                  iim*(jjm+1)*llm, ndex3d)  
527           endif           endif
528    
529           CALL gr_fi_ecrit(llm, klon, iim, jjm+1, d_tr_th(1, 1, it), zx_tmp_3d)           CALL gr_fi_ecrit(llm, klon, iim, jjm+1, d_tr_th(1, 1, it), zx_tmp_3d)
530           CALL histwrite(nid_tra, "d_tr_th_"//tnom(it+2), itau_w, zx_tmp_3d, &           CALL histwrite(nid_tra, "d_tr_th_"//tnom(it+2), itau_w, zx_tmp_3d)
               iim*(jjm+1)*llm, ndex3d)  
531           CALL gr_fi_ecrit(llm, klon, iim, jjm+1, d_tr_cv(1, 1, it), zx_tmp_3d)           CALL gr_fi_ecrit(llm, klon, iim, jjm+1, d_tr_cv(1, 1, it), zx_tmp_3d)
532           CALL histwrite(nid_tra, "d_tr_cv_"//tnom(it+2), itau_w, zx_tmp_3d, &           CALL histwrite(nid_tra, "d_tr_cv_"//tnom(it+2), itau_w, zx_tmp_3d)
               iim*(jjm+1)*llm, ndex3d)  
533           CALL gr_fi_ecrit(llm, klon, iim, jjm+1, d_tr_cl(1, 1, it), zx_tmp_3d)           CALL gr_fi_ecrit(llm, klon, iim, jjm+1, d_tr_cl(1, 1, it), zx_tmp_3d)
534           CALL histwrite(nid_tra, "d_tr_cl_"//tnom(it+2), itau_w, zx_tmp_3d, &           CALL histwrite(nid_tra, "d_tr_cl_"//tnom(it+2), itau_w, zx_tmp_3d)
               iim*(jjm+1)*llm, ndex3d)  
535        ENDDO        ENDDO
536    
       CALL gr_fi_ecrit(1, klon, iim, jjm+1, yu1, zx_tmp_2d)  
       CALL histwrite(nid_tra, "pyu1", itau_w, zx_tmp_2d, &  
            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)  
537        CALL gr_fi_ecrit(llm, klon, iim, jjm+1, pplay, zx_tmp_3d)        CALL gr_fi_ecrit(llm, klon, iim, jjm+1, pplay, zx_tmp_3d)
538        CALL histwrite(nid_tra, "pplay", itau_w, zx_tmp_3d, &        CALL histwrite(nid_tra, "pplay", itau_w, zx_tmp_3d)
            iim*(jjm+1)*llm, ndex3d)  
539    
540        CALL gr_fi_ecrit(llm, klon, iim, jjm+1, t_seri, zx_tmp_3d)        CALL gr_fi_ecrit(llm, klon, iim, jjm+1, t_seri, zx_tmp_3d)
541        CALL histwrite(nid_tra, "t", itau_w, 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  
542    
543        if (ok_sync) then        if (ok_sync) then
544           call histsync(nid_tra)           call histsync(nid_tra)
# Line 624  contains Line 560  contains
560      use advtrac_m, only: niadv, tnom, ttext      use advtrac_m, only: niadv, tnom, ttext
561      use dimphy, only: klon      use dimphy, only: klon
562      use clesphys, only: ecrit_tra      use clesphys, only: ecrit_tra
563      use grid_change, only: gr_phy_write      use grid_change, only: gr_phy_write_2d
564      use phyetat0_m, only: rlon, rlat      use phyetat0_m, only: rlon, rlat
565    
566      INTEGER, intent(out):: nid_tra      INTEGER, intent(out):: nid_tra
# Line 647  contains Line 583  contains
583      !---------------------------------------------------------      !---------------------------------------------------------
584    
585      CALL ymds2ju(annee_ref, month=1, day=day_ref, sec=0.0, julian=zjulian)      CALL ymds2ju(annee_ref, month=1, day=day_ref, sec=0.0, julian=zjulian)
586      zx_lat(:, :) = gr_phy_write(rlat)      zx_lat(:, :) = gr_phy_write_2d(rlat)
587      CALL histbeg_totreg("histrac", iim, rlon(2:iim+1), jjm+1, zx_lat(1, :), &      CALL histbeg_totreg("histrac", rlon(2:iim+1), zx_lat(1, :), &
588           1, iim, 1, jjm+1, itau_phy, zjulian, pdtphys, nhori, nid_tra)           1, iim, 1, jjm+1, itau_phy, zjulian, pdtphys, nhori, nid_tra)
589      CALL histvert(nid_tra, "presnivs", "Vertical levels", "mb", llm, &      CALL histvert(nid_tra, "presnivs", "Vertical levels", "mb", llm, &
590           presnivs, nvert)           presnivs, nvert)
# Line 657  contains Line 593  contains
593      zout = pdtphys * REAL(ecrit_tra)      zout = pdtphys * REAL(ecrit_tra)
594    
595      CALL histdef(nid_tra, "phis", "Surface geop. height", "-", &      CALL histdef(nid_tra, "phis", "Surface geop. height", "-", &
596           iim, jjm+1, nhori, 1, 1, 1, -99, 32, &           iim, jjm+1, nhori, 1, 1, 1, -99, &
597           "once",  zsto, zout)           "once",  zsto, zout)
598      CALL histdef(nid_tra, "aire", "Grid area", "-", &      CALL histdef(nid_tra, "aire", "Grid area", "-", &
599           iim, jjm+1, nhori, 1, 1, 1, -99, 32, &           iim, jjm+1, nhori, 1, 1, 1, -99, &
600           "once",  zsto, zout)           "once",  zsto, zout)
601      CALL histdef(nid_tra, "zmasse", "column density of air in cell", &      CALL histdef(nid_tra, "zmasse", "column density of air in cell", &
602           "kg m-2", iim, jjm + 1, nhori, llm, 1, llm, nvert, 32, "ave(X)", &           "kg m-2", iim, jjm + 1, nhori, llm, 1, llm, nvert, "ave(X)", &
603           zsto, zout)           zsto, zout)
604    
605      DO it=1, nqmax      DO it = 1, nqmax
606         ! champ 2D         ! champ 2D
607         iq=it+2         iq=it+2
608         iiq=niadv(iq)         iiq=niadv(iq)
609         CALL histdef(nid_tra, tnom(iq), ttext(iiq), "U/kga", iim, jjm+1, &         CALL histdef(nid_tra, tnom(iq), ttext(iiq), "U/kga", iim, jjm+1, &
610              nhori, llm, 1, llm, nvert, 32, "ave(X)", zsto, zout)              nhori, llm, 1, llm, nvert, "ave(X)", zsto, zout)
611         if (lessivage) THEN         if (lessivage) THEN
612            CALL histdef(nid_tra, "fl"//tnom(iq), "Flux "//ttext(iiq), &            CALL histdef(nid_tra, "fl"//tnom(iq), "Flux "//ttext(iiq), &
613                 "U/m2/s", iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &                 "U/m2/s", iim, jjm+1, nhori, llm, 1, llm, nvert, &
614                 "ave(X)", zsto, zout)                 "ave(X)", zsto, zout)
615         endif         endif
616    
617         !---Ajout Olivia         !---Ajout Olivia
618         CALL histdef(nid_tra, "d_tr_th_"//tnom(iq), &         CALL histdef(nid_tra, "d_tr_th_"//tnom(iq), &
619              "tendance thermique"// ttext(iiq), "?", &              "tendance thermique"// ttext(iiq), "?", &
620              iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &              iim, jjm+1, nhori, llm, 1, llm, nvert, &
621              "ave(X)", zsto, zout)              "ave(X)", zsto, zout)
622         CALL histdef(nid_tra, "d_tr_cv_"//tnom(iq), &         CALL histdef(nid_tra, "d_tr_cv_"//tnom(iq), &
623              "tendance convection"// ttext(iiq), "?", &              "tendance convection"// ttext(iiq), "?", &
624              iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &              iim, jjm+1, nhori, llm, 1, llm, nvert, &
625              "ave(X)", zsto, zout)              "ave(X)", zsto, zout)
626         CALL histdef(nid_tra, "d_tr_cl_"//tnom(iq), &         CALL histdef(nid_tra, "d_tr_cl_"//tnom(iq), &
627              "tendance couche limite"// ttext(iiq), "?", &              "tendance couche limite"// ttext(iiq), "?", &
628              iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &              iim, jjm+1, nhori, llm, 1, llm, nvert, &
629              "ave(X)", zsto, zout)              "ave(X)", zsto, zout)
630         !---fin Olivia             !---fin Olivia    
631    
632      ENDDO      ENDDO
633    
634      CALL histdef(nid_tra, "pyu1", "Vent niv 1", "-", &      CALL histdef(nid_tra, "pplay", "", "-", &
635           iim, jjm+1, nhori, 1, 1, 1, -99, 32, &           iim, jjm+1, nhori, llm, 1, llm, nvert, &
          "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, &  
636           "inst(X)", zout, zout)           "inst(X)", zout, zout)
637      CALL histdef(nid_tra, "t", "flux u mont", "-", &      CALL histdef(nid_tra, "t", "", "-", &
638           iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &           iim, jjm+1, nhori, llm, 1, llm, nvert, &
639           "inst(X)", zout, zout)           "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)  
640    
641      CALL histend(nid_tra)      CALL histend(nid_tra)
642    
# Line 774  contains Line 658  contains
658    
659      use dimens_m, only: llm      use dimens_m, only: llm
660      use dimphy, only: klon, nbtr      use dimphy, only: klon, nbtr
661      use nrutil, only: assert      use numer_rec, only: assert
662    
663      IMPLICIT none      IMPLICIT none
664    
# Line 810  contains Line 694  contains
694    
695      use dimens_m, only: llm      use dimens_m, only: llm
696      use dimphy, only: klon      use dimphy, only: klon
697      use nrutil, only: assert      use numer_rec, only: assert
698    
699      IMPLICIT none      IMPLICIT none
700    

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

  ViewVC Help
Powered by ViewVC 1.1.21