Changeset 619


Ignore:
Timestamp:
Apr 15, 2005, 2:36:17 PM (19 years ago)
Author:
lmdzadmin
Message:

Rajout convection Kerry Emanuel pour traceurs- MAF+JYG

Location:
LMDZ4/trunk/libf/phylmd
Files:
1 added
8 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/trunk/libf/phylmd/concvl.F

    r559 r619  
    77     .             upwd,dnwd,dnwdbis,Ma,cape,tvp,iflag,
    88     .             pbase,bbase,dtvpdt1,dtvpdq1,dplcldt,dplcldr,
    9      .             qcondc,wd)
     9     .             qcondc,wd,
     10     .             pmflxr,pmflxs,
     11     .             da,phi,mp)
    1012 
    1113c
     
    5658       INTEGER ntra
    5759       REAL work1(klon,klev),work2(klon,klev)
     60       REAL pmflxr(klon,klev+1),pmflxs(klon,klev+1)
    5861c
    5962       REAL d_t(klon,klev),d_q(klon,klev),d_u(klon,klev),d_v(klon,klev)
     
    6568       REAL upwd(klon,klev),dnwd(klon,klev),dnwdbis(klon,klev)
    6669       REAL Ma(klon,klev),cape(klon),tvp(klon,klev)
     70       real da(klon,klev),phi(klon,klev,klev),mp(klon,klev)
    6771       INTEGER iflag(klon)
    6872       REAL rflag(klon)
     
    101105         DO i=1,klon
    102106         em_ph(i,k) = paprs(i,k) / 100.0
     107         pmflxs(i,k)=0.
    103108      ENDDO
    104109      ENDDO
     
    145150     $              em_p,em_ph,iflag,
    146151     $              d_t,d_q,d_u,d_v,d_tra,rain,
    147      $              cbmf,work1,work2,
    148      $              dtime,Ma,upwd,dnwd,dnwdbis,qcondc,wd,cape)
     152     $              pmflxr,cbmf,work1,work2,
     153     $              kbas,ktop,
     154     $              dtime,Ma,upwd,dnwd,dnwdbis,qcondc,wd,cape,
     155     $              da,phi,mp)
    149156
    150157C------------------------------------------------------------------
     
    163170        ENDDO
    164171      ENDDO
    165  
     172       DO itra = 1,ntra
     173        DO k = 1, klev
     174         DO i = 1, klon
     175            d_tra(i,k,itra) =dtime*d_tra(i,k,itra)
     176         ENDDO
     177        ENDDO
     178       ENDDO
    166179c les traceurs ne sont pas mis dans cette version de convect4:
    167180      if (iflag_con.eq.4) then
  • LMDZ4/trunk/libf/phylmd/cv3_routines.F

    r597 r619  
    21642164     :                    ,ment,qent,uent,vent,nent,elij,traent,sig
    21652165     :                    ,tv,tvp
    2166      :                    ,iflag,precip,ft,fr,fu,fv,ftra
     2166     :                    ,iflag,precip,VPrecip,ft,fr,fu,fv,ftra
    21672167     :                    ,upwd,dnwd,dnwd0,ma,mike,tls,tps,qcondc,wd)
    21682168      implicit none
     
    21972197c outputs:
    21982198      real precip(nloc)
     2199      real VPrecip(nloc,nd+1)
    21992200      real ft(nloc,nd), fr(nloc,nd), fu(nloc,nd), fv(nloc,nd)
    22002201      real ftra(nloc,nd,ntra)
     
    22282229       precip(il)=0.0
    22292230       wd(il)=0.0     ! gust
     2231       VPrecip(il,nd+1)=0.
    22302232      enddo
    22312233
    22322234      do i=1,nd
    22332235       do il=1,ncum
     2236         VPrecip(il,i)=0.0
    22342237         ft(il,i)=0.0
    22352238         fr(il,i)=0.0
     
    22702273      enddo
    22712274
     2275C   ***  CALCULATE VERTICAL PROFILE OF  PRECIPITATIONs IN kg/m2/s  ===
     2276C
     2277c MAF rajout pour lessivage
     2278       do k=1,nl
     2279         do il=1,ncum
     2280          if (k.le.inb(il)) then
     2281            if (cvflag_grav) then
     2282             VPrecip(il,k) = wt(il,k)*sigd*water(il,k)/grav
     2283            else
     2284             VPrecip(il,k) = wt(il,k)*sigd*water(il,k)/10.
     2285            endif
     2286          endif
     2287         end do
     2288       end do
     2289C
    22722290c
    22732291c   ***  Calculate downdraft velocity scale    ***
     
    30253043      SUBROUTINE cv3_uncompress(nloc,len,ncum,nd,ntra,idcum
    30263044     :         ,iflag
    3027      :         ,precip,sig,w0
     3045     :         ,precip,VPrecip,sig,w0
    30283046     :         ,ft,fq,fu,fv,ftra
     3047     :         ,inb
    30293048     :         ,Ma,upwd,dnwd,dnwd0,qcondc,wd,cape
     3049     :         ,da,phi,mp
    30303050     :         ,iflag1
    3031      :         ,precip1,sig1,w01
     3051     :         ,precip1,VPrecip1,sig1,w01
    30323052     :         ,ft1,fq1,fu1,fv1,ftra1
     3053     :         ,inb1
    30333054     :         ,Ma1,upwd1,dnwd1,dnwd01,qcondc1,wd1,cape1
    3034      :                               )
     3055     :         ,da1,phi1,mp1)
    30353056      implicit none
    30363057
     
    30413062      integer idcum(nloc)
    30423063      integer iflag(nloc)
     3064      integer inb(nloc)
    30433065      real precip(nloc)
     3066      real VPrecip(nloc,nd+1)
    30443067      real sig(nloc,nd), w0(nloc,nd)
    30453068      real ft(nloc,nd), fq(nloc,nd), fu(nloc,nd), fv(nloc,nd)
     
    30493072      real qcondc(nloc,nd)
    30503073      real wd(nloc),cape(nloc)
     3074      real da(nloc,nd),phi(nloc,nd,nd),mp(nloc,nd)
    30513075
    30523076c outputs:
    30533077      integer iflag1(len)
     3078      integer inb1(len)
    30543079      real precip1(len)
     3080      real VPrecip1(len,nd+1)
    30553081      real sig1(len,nd), w01(len,nd)
    30563082      real ft1(len,nd), fq1(len,nd), fu1(len,nd), fv1(len,nd)
     
    30603086      real qcondc1(nloc,nd)
    30613087      real wd1(nloc),cape1(nloc)
     3088      real da1(nloc,nd),phi1(nloc,nd,nd),mp1(nloc,nd)
    30623089
    30633090c local variables:
     
    30683095         iflag1(idcum(i))=iflag(i)
    30693096         wd1(idcum(i))=wd(i)
     3097         inb1(idcum(i))=inb(i)
    30703098         cape1(idcum(i))=cape(i)
    30713099 2000   continue
     
    30733101        do 2020 k=1,nl
    30743102          do 2010 i=1,ncum
     3103            VPrecip1(idcum(i),k)=VPrecip(i,k)
    30753104            sig1(idcum(i),k)=sig(i,k)
    30763105            w01(idcum(i),k)=w0(i,k)
     
    30843113            dnwd01(idcum(i),k)=dnwd0(i,k)
    30853114            qcondc1(idcum(i),k)=qcondc(i,k)
     3115            da1(idcum(i),k)=da(i,k)
     3116            mp1(idcum(i),k)=mp(i,k)
    30863117 2010     continue
    30873118 2020   continue
     
    30993130c 2110    continue
    31003131c 2100   continue
     3132        do j=1,nd
     3133         do k=1,nd
     3134          do i=1,ncum
     3135            phi1(idcum(i),k,j)=phi(i,k,j)
     3136          end do
     3137         end do
     3138        end do
    31013139
    31023140        return
  • LMDZ4/trunk/libf/phylmd/cv_driver.F

    r559 r619  
    55     &                   t1,q1,qs1,u1,v1,tra1,
    66     &                   p1,ph1,iflag1,ft1,fq1,fu1,fv1,ftra1,
    7      &                   precip1,
     7     &                   precip1,VPrecip1,
    88     &                   cbmf1,sig1,w01,
    9      &                   delt,Ma1,upwd1,dnwd1,dnwd01,qcondc1,wd1,cape1)
     9     &                   icb1,inb1,
     10     &                   delt,Ma1,upwd1,dnwd1,dnwd01,qcondc1,wd1,cape1,
     11     &                   da1,phi1,mp1)
    1012C
    1113      implicit none
     
    3739C      ftra1         Real           Output       tracor tend
    3840C      precip1       Real           Output       precipitation
     41C      VPrecip1      Real           Output       vertical profile of precipitations
    3942C      cbmf1         Real           Output       cloud base mass flux
    4043C      sig1          Real           In/Out       section adiabatic updraft
     
    8487      real precip1(len)
    8588      real cbmf1(len)
     89      real VPrecip1(len,nd+1)
    8690      real Ma1(len,nd)
    8791      real upwd1(len,nd)
     
    9397      real cape1(len)     
    9498
     99      real da1(len,nd),phi1(len,nd,nd),mp1(len,nd)
     100      real da(len,nd),phi(len,nd,nd),mp(len,nd)
    95101      real tra1(len,nd,ntra)
    96102      real ftra1(len,nd,ntra)
     
    185191!  precip: Scalar convective precipitation rate (mm/day).
    186192!
     193!  VPrecip: Vertical profile of convective precipitation (kg/m2/s).
     194!
    187195!  wd:   A convective downdraft velocity scale. For use in surface
    188196!        flux parameterizations. See convect.ps file for details.
     
    213221      integer nk1(klon)
    214222      integer icb1(klon)
     223      integer inb1(klon)
    215224      integer icbs1(klon)
    216225
     
    267276      real ments(nloc,klev,klev), qents(nloc,klev,klev)
    268277      real sij(nloc,klev,klev), elij(nloc,klev,klev)
    269       real mp(nloc,klev), qp(nloc,klev), up(nloc,klev), vp(nloc,klev)
     278      real qp(nloc,klev), up(nloc,klev), vp(nloc,klev)
    270279      real wt(nloc,klev), water(nloc,klev), evap(nloc,klev)
    271280      real b(nloc,klev), ft(nloc,klev), fq(nloc,klev)
     
    275284      real tps(nloc,klev), qprime(nloc), tprime(nloc)
    276285      real precip(nloc)
     286      real VPrecip(nloc,klev+1)
    277287      real tra(nloc,klev,ntra), trap(nloc,klev,ntra)
    278288      real ftra(nloc,klev,ntra), traent(nloc,klev,klev,ntra)
     
    324334         clw(i,k)=0.0   
    325335         gz1(i,k) = 0.
    326 
     336         VPrecip1(i,k) = 0.
    327337         Ma1(i,k)=0.0
    328338         upwd1(i,k)=0.0
     
    346356        wd1(i)=0.0
    347357        cape1(i)=0.0
     358        VPrecip1(i,nd+1)=0.0
    348359 60   continue
    349360
     
    552563     :                     ,ment,qent,uent,vent,nent,elij,traent,sig
    553564     :                     ,tv,tvp
    554      o                     ,iflag,precip,ft,fq,fu,fv,ftra
     565     o                     ,iflag,precip,VPrecip,ft,fq,fu,fv,ftra
    555566     o                     ,upwd,dnwd,dnwd0,ma,mike,tls,tps,qcondc,wd)
    556567      endif
     
    568579
    569580!^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
     581! --- passive tracers
     582!^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
     583
     584      if (iflag_con.eq.3) then
     585       CALL cv3_tracer(nloc,len,ncum,nd,nd,
     586     :                  ment,sij,da,phi)
     587      endif
     588
     589!^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
    570590! --- UNCOMPRESS THE FIELDS
    571591!^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
    572 
    573 
     592c set iflag1 =42 for non convective points
     593      do  i=1,len
     594        iflag1(i)=42
     595      end do
     596c
    574597      if (iflag_con.eq.3) then
    575598       CALL cv3_uncompress(nloc,len,ncum,nd,ntra,idcum
    576599     :          ,iflag
    577      :          ,precip,sig,w0
     600     :          ,precip,VPrecip,sig,w0
    578601     :          ,ft,fq,fu,fv,ftra
     602     :          ,inb
    579603     :          ,Ma,upwd,dnwd,dnwd0,qcondc,wd,cape
     604     :          ,da,phi,mp
    580605     o          ,iflag1
    581      o          ,precip1,sig1,w01
     606     o          ,precip1,VPrecip1,sig1,w01
    582607     o          ,ft1,fq1,fu1,fv1,ftra1
    583      o          ,Ma1,upwd1,dnwd1,dnwd01,qcondc1,wd1,cape1 )
     608     o          ,inb1
     609     o          ,Ma1,upwd1,dnwd1,dnwd01,qcondc1,wd1,cape1
     610     o          ,da1,phi1,mp1)
    584611      endif
    585612
     
    611638c -- si .TRUE., on rend la gravite plus explicite et eventuellement
    612639c differente de 10.0 dans convect3:
    613       cvflag_grav = .FALSE.
     640      cvflag_grav = .TRUE.
    614641
    615642      return
     
    654681c ori      t0  = RTT
    655682       t0  = 273.15 ! convect3 (RTT=273.16)
    656        grav= 10.    ! implicitely or explicitely used in convect3
     683c maf       grav= 10.    ! implicitely or explicitely used in convect3
     684       grav= g    ! implicitely or explicitely used in convect3
    657685      endif
    658686
  • LMDZ4/trunk/libf/phylmd/ini_histmth.h

    r602 r619  
    538538     .                "ave(X)", zsto,zout)
    539539c
    540          CALL histdef(nid_mth, "upwd", "saturated updraft", "kg/m2/s",
    541      .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
    542      .                "ave(X)", zsto,zout)
    543 c
    544540         CALL histdef(nid_mth, "dtphy", "Physics dT", "K/s",
    545541     .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
     
    594590     .                "ave(X)", zsto,zout)
    595591c
     592      IF (iflag_con.GE.3) THEN
     593c
    596594         CALL histdef(nid_mth,"Ma","undilute adiab updraft","kg/m2/s",
    597595     .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
    598596     .                "ave(X)", zsto,zout)
    599597c
     598         CALL histdef(nid_mth, "upwd", "saturated updraft", "kg/m2/s",
     599     .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
     600     .                "ave(X)", zsto,zout)
     601c
    600602         CALL histdef(nid_mth, "dnwd", "saturated downdraft","kg/m2/s",
    601603     .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
     
    605607     .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
    606608     .                "ave(X)", zsto,zout)
     609      ENDIF !iflag_con.GE.3
     610c
    607611c
    608612         CALL histdef(nid_mth, "dtdyn", "Dynamics dT", "K/s",
     
    741745c
    742746         if (nqmax.GE.3) THEN
    743          DO iq=1,nqmax-2
    744          IF (iq.LE.99) THEN
    745          WRITE(str2,'(i2.2)') iq
    746          CALL histdef(nid_mth, "trac"//str2, "Tracer No."//str2, "-",
    747      .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
    748      .                "ave(X)", zsto,zout)
    749          ELSE
    750          PRINT*, "Trop de traceurs"
    751          CALL abort
    752          ENDIF
     747         DO iq=3,nqmax
     748         iiq=niadv(iq)
     749         CALL histdef(nid_mth, tnom(iq), ttext(iiq), "-",
     750     .                iim,jjmp1,nhori, klev,1,klev,nvert, 32,
     751     .                "ave(X)", zsto,zout)
    753752         ENDDO
    754753         ENDIF
  • LMDZ4/trunk/libf/phylmd/physiq.F

    r616 r619  
    212212      REAL d_qx(klon,klev,nqmax)
    213213      REAL d_ps(klon)
     214      real da(klon,klev),phi(klon,klev,klev),mp(klon,klev)
    214215
    215216      INTEGER klevp1, klevm1
     
    769770      REAL zx_t, zx_qs, zdelta, zcor, zfra, zlvdcp, zlsdcp
    770771      real zqsat(klon,klev)
    771       INTEGER i, k, iq, ig, j, nsrf, ll
     772      INTEGER i, k, iq, ig, j, iiq, nsrf, ll
    772773      REAL t_coup
    773774      PARAMETER (t_coup=234.0)
     
    795796      INTEGER iflagctrl(klon)          ! flag fonctionnement de convect
    796797c -- convect43:
    797       INTEGER ntra              ! nb traceurs pour convect4.3
     798      INTEGER ntra              ! nb traceurs
    798799      REAL pori_con(klon)    ! pressure at the origin level of lifted parcel
    799800      REAL plcl_con(klon),dtma_con(klon),dtlcl_con(klon)
     
    11531154
    11541155         WRITE(lunout,*)"*** Convection de Kerry Emanuel 4.3  "
    1155          WRITE(lunout,*)
    1156      .      "On va utiliser le melange convectif des traceurs qui"
    1157          WRITE(lunout,*)"est calcule dans convect4.3"
    1158          WRITE(lunout,*)" !!! penser aux logical flags de phytrac"
    11591156
    11601157          DO i = 1, klon
     
    11671164          DO i = 1, klon
    11681165           ibas_con(i) = 1
    1169            itop_con(i) = klev+1
     1166           itop_con(i) = 1
    11701167          ENDDO
    11711168cIM15/11/02 rajout initialisation ibas_con,itop_con cf. SB =>END
     
    17331730      ELSE IF (iflag_con.GE.3) THEN
    17341731c nb of tracers for the KE convection:
    1735           if (nqmax .GE. 4) then
    1736               ntra = nbtr
    1737           else
    1738               ntra = 1
    1739           endif
    1740 c
     1732c MAF la partie traceurs est faite dans phytrac
     1733c on met ntra=1 pour limiter les appels mais on peut
     1734c supprimer les calculs / ftra.
     1735              ntra = 1
    17411736c sb, oct02:
    17421737c Schema de convection modularise et vectorise:
     
    17471742          CALL concvl (iflag_con,
    17481743     .        dtime,paprs,pplay,t_seri,q_seri,
    1749      .        u_seri,v_seri,tr_seri,nbtr,
     1744     .        u_seri,v_seri,tr_seri,ntra,
    17501745     .        ema_work1,ema_work2,
    17511746     .        d_t_con,d_q_con,d_u_con,d_v_con,d_tr,
     
    17531748     .        upwd,dnwd,dnwd0,
    17541749     .        Ma,cape,tvp,iflagctrl,
    1755      .        pbase,bbase,dtvpdt1,dtvpdq1,dplcldt,dplcldr,qcondc,wd)
     1750     .        pbase,bbase,dtvpdt1,dtvpdq1,dplcldt,dplcldr,qcondc,wd,
     1751     .        pmflxr,pmflxs,
     1752     .        da,phi,mp)
     1753
    17561754cIM cf. FH
    17571755              clwcon0=qcondc
     1756              pmfu(:,:)=upwd(:,:)+dnwd(:,:)
    17581757
    17591758          ELSE ! ok_cvl
    1760 
     1759c MAF conema3 ne contient pas les traceurs
    17611760          CALL conema3 (dtime,
    17621761     .        paprs,pplay,t_seri,q_seri,
    1763      .        u_seri,v_seri,tr_seri,nbtr,
     1762     .        u_seri,v_seri,tr_seri,ntra,
    17641763     .        ema_work1,ema_work2,
    17651764     .        d_t_con,d_q_con,d_u_con,d_v_con,d_tr,
     
    18851884      zx_ajustq=.FALSE.
    18861885c
    1887       IF (nqmax.GT.2) THEN !--melange convectif de traceurs
    1888 c
    1889           IF (iflag_con .NE. 2 .AND. debut) THEN
    1890               WRITE(lunout,*)'Pour l instant, seul conflx fonctionne ',
    1891      $            'avec traceurs', iflag_con
    1892               WRITE(lunout,*)' Mettre iflag_con',
    1893      $            ' = 2 dans run.def et repasser'
    1894 c              CALL abort
    1895               ENDIF
    1896 c
    1897       ENDIF !--nqmax.GT.2
    1898 c
    1899 c Appeler l'ajustement sec
    1900 c
    19011886c===================================================================
    19021887c Convection seche (thermiques ou ajustement)
     
    26442629c   Calcul  des tendances traceurs
    26452630c====================================================================
    2646 C Pascale : il faut quand meme apeller phytrac car il gere les sorties
    2647 cKE43       des traceurs => il faut donc mettre des flags a .false.
    2648       IF (iflag_con.GE.3) THEN
    2649 c           on ajoute les tendances calculees par KE43
    2650 cXXX OM on onhibe la convection sur les traceurs
    2651         DO iq=1, nqmax-2 ! Sandrine a -3 ???
    2652 cXXX OM on inhibe la convection sur les traceur
    2653 cXXX        DO k = 1, nlev
    2654 cXXX        DO i = 1, klon
    2655 cXXX          tr_seri(i,k,iq) = tr_seri(i,k,iq) + d_tr(i,k,iq)
    2656 cXXX        ENDDO
    2657 cXXX        ENDDO
    2658         WRITE(iqn,'(i2.2)') iq
    2659         CALL minmaxqfi(tr_seri(1,1,iq),0.,1.e33,'couche lim iq='//iqn)
    2660         ENDDO
    2661 CMAF modif pour garder info du nombre de traceurs auxquels
    2662 C la physique s'applique
    2663       ELSE
    2664 CMAF modif pour garder info du nombre de traceurs auxquels
    2665 C la physique s'applique
    26662631C
    2667       call phytrac (rnpb,
     2632      call phytrac (iflag_con,rnpb,
    26682633     I                   itap, julien, gmtime,
    26692634     I                   debut,lafin,
     
    26802645     I                   ibas_con,
    26812646     I                   pmflxr,pmflxs,prfl,psfl,
    2682 #ifdef INCA
     2647     I                   da,phi,mp,
     2648     I                   upwd,dnwd,
     2649#ifdef INCA_CH4
    26832650     I                   flxmass_w,
    26842651#endif
    26852652     O                   tr_seri)
    2686       ENDIF
    26872653
    26882654      IF (offline) THEN
  • LMDZ4/trunk/libf/phylmd/phytrac.F

    r616 r619  
    44c
    55c
    6       SUBROUTINE phytrac (rnpb,nstep,
     6      SUBROUTINE phytrac (iflag_con,rnpb,nstep,
    77     I                    julien,gmtime,
    88     I                    debutphy,lafin,
     
    146146      REAL flxmass_w(klon,klev)
    147147#endif
     148      integer iflag_con
    148149
    149150cAA Rem : nbtr : nombre de vrais traceurs est defini dans dimphy.h
     
    166167      REAL pen_d(nlon,nlev) ! flux entraine dans le panache descendant
    167168      REAL pde_d(nlon,nlev) ! flux detraine dans le panache descendant
     169c KE
     170      real da(nlon,nlev),phi(nlon,nlev,nlev),mp(nlon,nlev)
     171      REAL upwd(nlon,nlev)      ! saturated updraft mass flux
     172      REAL dnwd(nlon,nlev)      ! saturated downdraft mass flux
     173
    168174c
    169175c   Couche limite:
     
    281287c
    282288      REAL d_tr(klon,klev), d_trs(klon) ! tendances de traceurs
    283       REAL d_tr_cl(klon,klev) ! tendance de traceurs  couche limite
    284       REAL d_tr_cli(klon,klev,nbtr) ! tendance de traceurs  CL pour chq traceur
    285       REAL d_tr_cv(klon,klev) ! tendance de traceurs  convection
    286       REAL d_tr_cvi(klon,klev,nbtr) ! tendance de traceurs  conv pour chq traceur
     289      REAL d_tr_cl(klon,klev,nbtr) ! tendance de traceurs  couche limite
     290      REAL d_tr_cv(klon,klev,nbtr) ! tendance de traceurs  conv pour chq traceur
    287291      REAL d_tr_th(klon,klev,nbtr) ! la tendance des thermiques
    288292      REAL d_tr_dec(klon,klev,nbtr) ! la tendance de la decroissance
     
    528532
    529533c Abder
    530       if(nqmax.gt.2) aerosol(3)=.true.
     534ctestmaf      if(nqmax.gt.2) aerosol(3)=.true.
    531535
    532536       do i=1,nlon
     
    548552c======================================================================
    549553c     print*,'Avant convection'
    550       do it=1,nqmax
    551          WRITE(itn,'(i2)') it
     554c      do it=1,nqmax
     555c         WRITE(itn,'(i2)') it
    552556c        call diagtracphy(tr_seri(:,:,it),paprs,'Avant conv'//itn)
    553       enddo
     557c      enddo
    554558
    555559      if (convection) then
     
    560564      IF ( conv_flg(it) == 0 ) CYCLE
    561565#endif
     566      if (iflag_con.eq.2) then
     567c tiedke
    562568      CALL nflxtr(pdtphys, pmfu, pmfd, pen_u, pde_u, pen_d, pde_d,
    563      .            pplay, paprs, tr_seri(1,1,it), d_tr_cv)
     569     .            pplay, paprs, tr_seri(1,1,it), d_tr_cv(1,1,it))
     570      else if (iflag_con.eq.3) then
     571c KE
     572      call cvltr(pdtphys, da, phi, mp, paprs,pplay, tr_seri(1,1,it),
     573     .           upwd,dnwd,d_tr_cv(1,1,it))
     574      endif
     575
    564576      DO k = 1, nlev
    565577      DO i = 1, klon
    566          tr_seri(i,k,it) = tr_seri(i,k,it) + d_tr_cv(i,k)
    567          d_tr_cvi(i,k,it)=d_tr_cv(i,k)
    568 c        print*,'en k i d_tr_cv=',k,i,d_tr_cv(i,k)
     578         tr_seri(i,k,it) = tr_seri(i,k,it) + d_tr_cv(i,k,it)
    569579      ENDDO
    570580      ENDDO
    571 c      WRITE(itn,'(i1)') it
    572581#ifdef INCA
    573582      CALL minmaxqfi(tr_seri(1,1,it),0.,1.e33,'convection it = '
     
    676685     e                    tautr(it),vdeptr(it),
    677686     e                    xlat,
    678      s                    d_tr_cl,d_trs)
     687     s                    d_tr_cl(1,1,it),d_trs)
    679688          DO k = 1, nlev
    680689            DO i = 1, klon
    681               tr_seri(i,k,it) = tr_seri(i,k,it) + d_tr_cl(i,k)
    682               d_tr_cli(i,k,it)=d_tr_cl(i,k)
     690              tr_seri(i,k,it) = tr_seri(i,k,it) + d_tr_cl(i,k,it)
    683691            ENDDO
    684692          ENDDO
     
    709717     s               tr_seri(1,1,it), source,
    710718     e               paprs, pplay, delp,
    711      s               d_tr )
     719     s               d_tr_cl(1,1,it))
    712720            DO k = 1, nlev
    713721               DO i = 1, klon
    714                   tr_seri(i,k,it) = tr_seri(i,k,it) + d_tr(i,k)
    715                   d_tr_cli(i,k,it)=d_tr_cl(i,k)
     722                  tr_seri(i,k,it) = tr_seri(i,k,it) + d_tr_cl(i,k,it)
    716723               ENDDO
    717724            ENDDO
    718 Cmaf provisoire suppression des prints
    719725Cmaf          WRITE(itn,'(i1)') it
    720726cmaf          CALL minmaxqfi(tr_seri(1,1,it),0.,1.e33,'cltracn it='//itn)
  • LMDZ4/trunk/libf/phylmd/write_histmth.h

    r602 r619  
    586586     .                                   iim*jjmp1*klev,ndex3d)
    587587c
     588      IF (iflag_con.GE.3) THEN
     589c
    588590      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, Ma, zx_tmp_3d)
    589591      CALL histwrite(nid_mth,"Ma",itau_w,zx_tmp_3d,
     
    602604     .                                   iim*jjmp1*klev,ndex3d)
    603605c
     606      ENDIF !iflag_con.GE.3
    604607c
    605608      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t_dyn, zx_tmp_3d)
     
    763766c
    764767      IF (nqmax.GE.3) THEN
    765       DO iq=1,nqmax-2
    766       IF (iq.LE.99) THEN
    767          CALL gr_fi_ecrit(klev,klon,iim,jjmp1, qx(1,1,iq+2), zx_tmp_3d)
    768          WRITE(str2,'(i2.2)') iq
    769          CALL histwrite(nid_mth,"trac"//str2,itau_w,zx_tmp_3d,
    770      .                                   iim*jjmp1*klev,ndex3d)
    771       ELSE
    772          PRINT*, "Trop de traceurs"
    773          CALL abort
    774       ENDIF
     768      DO iq=3,nqmax
     769         CALL gr_fi_ecrit(klev,klon,iim,jjmp1, qx(1,1,iq), zx_tmp_3d)
     770         CALL histwrite(nid_mth,tnom(iq),itau_w,zx_tmp_3d,
     771     .                                   iim*jjmp1*klev,ndex3d)
    775772      ENDDO
    776773      ENDIF
  • LMDZ4/trunk/libf/phylmd/write_histrac.h

    r616 r619  
    248248       CALL histwrite(nid_tra,"d_tr_th_"//tnom(it+2),itau_w,zx_tmp_3d,
    249249     .                                   iim*(jjm+1)*klev,ndex3d)
    250        CALL gr_fi_ecrit(klev,klon,iim,jjm+1,d_tr_cvi(1,1,it),zx_tmp_3d)
     250       CALL gr_fi_ecrit(klev,klon,iim,jjm+1,d_tr_cv(1,1,it),zx_tmp_3d)
    251251       CALL histwrite(nid_tra,"d_tr_cv_"//tnom(it+2),itau_w,zx_tmp_3d,
    252252     .                                   iim*(jjm+1)*klev,ndex3d)
    253        CALL gr_fi_ecrit(klev,klon,iim,jjm+1,d_tr_cli(1,1,it),zx_tmp_3d)
     253       CALL gr_fi_ecrit(klev,klon,iim,jjm+1,d_tr_cl(1,1,it),zx_tmp_3d)
    254254       CALL histwrite(nid_tra,"d_tr_cl_"//tnom(it+2),itau_w,zx_tmp_3d,
    255255     .                                   iim*(jjm+1)*klev,ndex3d)
Note: See TracChangeset for help on using the changeset viewer.