/[lmdze]/trunk/Sources/phylmd/cv_driver.f
ViewVC logotype

Diff of /trunk/Sources/phylmd/cv_driver.f

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

revision 49 by guez, Wed Aug 24 11:43:14 2011 UTC revision 62 by guez, Thu Jul 26 14:37:37 2012 UTC
# Line 1  Line 1 
1  !  module cv_driver_m
 ! $Header: /home/cvsroot/LMDZ4/libf/phylmd/cv_driver.F,v 1.3 2005/04/15 12:36:17 lmdzadmin Exp $  
 !  
       SUBROUTINE cv_driver(len,nd,ndp1,ntra,iflag_con, &  
                          t1,q1,qs1,u1,v1,tra1, &  
                          p1,ph1,iflag1,ft1,fq1,fu1,fv1,ftra1, &  
                          precip1,VPrecip1, &  
                          cbmf1,sig1,w01, &  
                          icb1,inb1, &  
                          delt,Ma1,upwd1,dnwd1,dnwd01,qcondc1,wd1,cape1, &  
                          da1,phi1,mp1)  
 !  
       use dimens_m  
       use dimphy  
       implicit none  
 !  
 !.............................START PROLOGUE............................  
 !  
 ! PARAMETERS:  
 !      Name            Type         Usage            Description  
 !   ----------      ----------     -------  ----------------------------  
 !  
 !      len           Integer        Input        first (i) dimension  
 !      nd            Integer        Input        vertical (k) dimension  
 !      ndp1          Integer        Input        nd + 1  
 !      ntra          Integer        Input        number of tracors  
 !      iflag_con     Integer        Input        version of convect (3/4)  
 !      t1            Real           Input        temperature  
 !      q1            Real           Input        specific hum  
 !      qs1           Real           Input        sat specific hum  
 !      u1            Real           Input        u-wind  
 !      v1            Real           Input        v-wind  
 !      tra1          Real           Input        tracors  
 !      p1            Real           Input        full level pressure  
 !      ph1           Real           Input        half level pressure  
 !      iflag1        Integer        Output       flag for Emanuel conditions  
 !      ft1           Real           Output       temp tend  
 !      fq1           Real           Output       spec hum tend  
 !      fu1           Real           Output       u-wind tend  
 !      fv1           Real           Output       v-wind tend  
 !      ftra1         Real           Output       tracor tend  
 !      precip1       Real           Output       precipitation  
 !      VPrecip1      Real           Output       vertical profile of precipitations  
 !      cbmf1         Real           Output       cloud base mass flux  
 !      sig1          Real           In/Out       section adiabatic updraft  
 !      w01           Real           In/Out       vertical velocity within adiab updraft  
 !      delt          Real           Input        time step  
 !      Ma1           Real           Output       mass flux adiabatic updraft  
 !      upwd1         Real           Output       total upward mass flux (adiab+mixed)  
 !      dnwd1         Real           Output       saturated downward mass flux (mixed)  
 !      dnwd01        Real           Output       unsaturated downward mass flux  
 !      qcondc1       Real           Output       in-cld mixing ratio of condensed water  
 !      wd1           Real           Output       downdraft velocity scale for sfc fluxes  
 !      cape1         Real           Output       CAPE  
 !  
 ! S. Bony, Mar 2002:  
 !     * Several modules corresponding to different physical processes  
 !     * Several versions of convect may be used:  
 !        - iflag_con=3: version lmd  (previously named convect3)  
 !        - iflag_con=4: version 4.3b (vect. version, previously convect1/2)  
 !   + tard:    - iflag_con=5: version lmd with ice (previously named convectg)  
 ! S. Bony, Oct 2002:  
 !     * Vectorization of convect3 (ie version lmd)  
 !  
 !..............................END PROLOGUE.............................  
 !  
 !  
   
       integer len  
       integer nd  
       integer ndp1  
       integer noff  
       integer, intent(in):: iflag_con  
       integer ntra  
       real t1(len,nd)  
       real q1(len,nd)  
       real qs1(len,nd)  
       real u1(len,nd)  
       real v1(len,nd)  
       real p1(len,nd)  
       real ph1(len,ndp1)  
       integer iflag1(len)  
       real ft1(len,nd)  
       real fq1(len,nd)  
       real fu1(len,nd)  
       real fv1(len,nd)  
       real precip1(len)  
       real cbmf1(len)  
       real VPrecip1(len,nd+1)  
       real Ma1(len,nd)  
       real upwd1(len,nd)  
       real dnwd1(len,nd)  
       real dnwd01(len,nd)  
   
       real qcondc1(len,nd)     ! cld  
       real wd1(len)            ! gust  
       real cape1(len)  
   
       real da1(len,nd),phi1(len,nd,nd),mp1(len,nd)  
       real da(len,nd),phi(len,nd,nd),mp(len,nd)  
       real, intent(in):: tra1(len,nd,ntra)  
       real ftra1(len,nd,ntra)  
   
       real, intent(in):: delt  
   
 !-------------------------------------------------------------------  
 ! --- ARGUMENTS  
 !-------------------------------------------------------------------  
 ! --- On input:  
 !  
 !  t:   Array of absolute temperature (K) of dimension ND, with first  
 !       index corresponding to lowest model level. Note that this array  
 !       will be altered by the subroutine if dry convective adjustment  
 !       occurs and if IPBL is not equal to 0.  
 !  
 !  q:   Array of specific humidity (gm/gm) of dimension ND, with first  
 !       index corresponding to lowest model level. Must be defined  
 !       at same grid levels as T. Note that this array will be altered  
 !       if dry convective adjustment occurs and if IPBL is not equal to 0.  
 !  
 !  qs:  Array of saturation specific humidity of dimension ND, with first  
 !       index corresponding to lowest model level. Must be defined  
 !       at same grid levels as T. Note that this array will be altered  
 !       if dry convective adjustment occurs and if IPBL is not equal to 0.  
 !  
 !  u:   Array of zonal wind velocity (m/s) of dimension ND, witth first  
 !       index corresponding with the lowest model level. Defined at  
 !       same levels as T. Note that this array will be altered if  
 !       dry convective adjustment occurs and if IPBL is not equal to 0.  
 !  
 !  v:   Same as u but for meridional velocity.  
 !  
 !  tra: Array of passive tracer mixing ratio, of dimensions (ND,NTRA),  
 !       where NTRA is the number of different tracers. If no  
 !       convective tracer transport is needed, define a dummy  
 !       input array of dimension (ND,1). Tracers are defined at  
 !       same vertical levels as T. Note that this array will be altered  
 !       if dry convective adjustment occurs and if IPBL is not equal to 0.  
 !  
 !  p:   Array of pressure (mb) of dimension ND, with first  
 !       index corresponding to lowest model level. Must be defined  
 !       at same grid levels as T.  
 !  
 !  ph:  Array of pressure (mb) of dimension ND+1, with first index  
 !       corresponding to lowest level. These pressures are defined at  
 !       levels intermediate between those of P, T, Q and QS. The first  
 !       value of PH should be greater than (i.e. at a lower level than)  
 !       the first value of the array P.  
 !  
 !  nl:  The maximum number of levels to which convection can penetrate, plus 1.  
 !       NL MUST be less than or equal to ND-1.  
 !  
 !  delt: The model time step (sec) between calls to CONVECT  
 !  
 !----------------------------------------------------------------------------  
 ! ---   On Output:  
 !  
 !  iflag: An output integer whose value denotes the following:  
 !       VALUE   INTERPRETATION  
 !       -----   --------------  
 !         0     Moist convection occurs.  
 !         1     Moist convection occurs, but a CFL condition  
 !               on the subsidence warming is violated. This  
 !               does not cause the scheme to terminate.  
 !         2     Moist convection, but no precip because ep(inb) lt 0.0001  
 !         3     No moist convection because new cbmf is 0 and old cbmf is 0.  
 !         4     No moist convection; atmosphere is not  
 !               unstable  
 !         6     No moist convection because ihmin le minorig.  
 !         7     No moist convection because unreasonable  
 !               parcel level temperature or specific humidity.  
 !         8     No moist convection: lifted condensation  
 !               level is above the 200 mb level.  
 !         9     No moist convection: cloud base is higher  
 !               then the level NL-1.  
 !  
 !  ft:   Array of temperature tendency (K/s) of dimension ND, defined at same  
 !        grid levels as T, Q, QS and P.  
 !  
 !  fq:   Array of specific humidity tendencies ((gm/gm)/s) of dimension ND,  
 !        defined at same grid levels as T, Q, QS and P.  
 !  
 !  fu:   Array of forcing of zonal velocity (m/s^2) of dimension ND,  
 !        defined at same grid levels as T.  
 !  
 !  fv:   Same as FU, but for forcing of meridional velocity.  
 !  
 !  ftra: Array of forcing of tracer content, in tracer mixing ratio per  
 !        second, defined at same levels as T. Dimensioned (ND,NTRA).  
 !  
 !  precip: Scalar convective precipitation rate (mm/day).  
 !  
 !  VPrecip: Vertical profile of convective precipitation (kg/m2/s).  
 !  
 !  wd:   A convective downdraft velocity scale. For use in surface  
 !        flux parameterizations. See convect.ps file for details.  
 !  
 !  tprime: A convective downdraft temperature perturbation scale (K).  
 !          For use in surface flux parameterizations. See convect.ps  
 !          file for details.  
 !  
 !  qprime: A convective downdraft specific humidity  
 !          perturbation scale (gm/gm).  
 !          For use in surface flux parameterizations. See convect.ps  
 !          file for details.  
 !  
 !  cbmf: The cloud base mass flux ((kg/m**2)/s). THIS SCALAR VALUE MUST  
 !        BE STORED BY THE CALLING PROGRAM AND RETURNED TO CONVECT AT  
 !        ITS NEXT CALL. That is, the value of CBMF must be "remembered"  
 !        by the calling program between calls to CONVECT.  
 !  
 !  det:   Array of detrainment mass flux of dimension ND.  
 !  
 !-------------------------------------------------------------------  
 !  
 !  Local arrays  
 !  
   
       integer i,k,n,il,j  
       integer icbmax  
       integer nk1(klon)  
       integer icb1(klon)  
       integer inb1(klon)  
       integer icbs1(klon)  
   
       real plcl1(klon)  
       real tnk1(klon)  
       real qnk1(klon)  
       real gznk1(klon)  
       real pnk1(klon)  
       real qsnk1(klon)  
       real pbase1(klon)  
       real buoybase1(klon)  
   
       real lv1(klon,klev)  
       real cpn1(klon,klev)  
       real tv1(klon,klev)  
       real gz1(klon,klev)  
       real hm1(klon,klev)  
       real h1(klon,klev)  
       real tp1(klon,klev)  
       real tvp1(klon,klev)  
       real clw1(klon,klev)  
       real sig1(klon,klev)  
       real w01(klon,klev)  
       real th1(klon,klev)  
 !  
       integer ncum  
 !  
 ! (local) compressed fields:  
 !  
       integer nloc  
       parameter (nloc=klon) ! pour l'instant  
   
       integer idcum(nloc)  
       integer iflag(nloc),nk(nloc),icb(nloc)  
       integer nent(nloc,klev)  
       integer icbs(nloc)  
       integer inb(nloc), inbis(nloc)  
   
       real cbmf(nloc),plcl(nloc),tnk(nloc),qnk(nloc),gznk(nloc)  
       real t(nloc,klev),q(nloc,klev),qs(nloc,klev)  
       real u(nloc,klev),v(nloc,klev)  
       real gz(nloc,klev),h(nloc,klev),lv(nloc,klev),cpn(nloc,klev)  
       real p(nloc,klev),ph(nloc,klev+1),tv(nloc,klev),tp(nloc,klev)  
       real clw(nloc,klev)  
       real dph(nloc,klev)  
       real pbase(nloc), buoybase(nloc), th(nloc,klev)  
       real tvp(nloc,klev)  
       real sig(nloc,klev), w0(nloc,klev)  
       real hp(nloc,klev), ep(nloc,klev), sigp(nloc,klev)  
       real frac(nloc), buoy(nloc,klev)  
       real cape(nloc)  
       real m(nloc,klev), ment(nloc,klev,klev), qent(nloc,klev,klev)  
       real uent(nloc,klev,klev), vent(nloc,klev,klev)  
       real ments(nloc,klev,klev), qents(nloc,klev,klev)  
       real sij(nloc,klev,klev), elij(nloc,klev,klev)  
       real qp(nloc,klev), up(nloc,klev), vp(nloc,klev)  
       real wt(nloc,klev), water(nloc,klev), evap(nloc,klev)  
       real b(nloc,klev), ft(nloc,klev), fq(nloc,klev)  
       real fu(nloc,klev), fv(nloc,klev)  
       real upwd(nloc,klev), dnwd(nloc,klev), dnwd0(nloc,klev)  
       real Ma(nloc,klev), mike(nloc,klev), tls(nloc,klev)  
       real tps(nloc,klev), qprime(nloc), tprime(nloc)  
       real precip(nloc)  
       real VPrecip(nloc,klev+1)  
       real tra(nloc,klev,ntra), trap(nloc,klev,ntra)  
       real ftra(nloc,klev,ntra), traent(nloc,klev,klev,ntra)  
       real qcondc(nloc,klev)  ! cld  
       real wd(nloc)           ! gust  
   
 !-------------------------------------------------------------------  
 ! --- SET CONSTANTS AND PARAMETERS  
 !-------------------------------------------------------------------  
   
 ! -- set simulation flags:  
 !   (common cvflag)  
   
        CALL cv_flag  
   
 ! -- set thermodynamical constants:  
 !     (common cvthermo)  
   
        CALL cv_thermo(iflag_con)  
   
 ! -- set convect parameters  
 !  
 !     includes microphysical parameters and parameters that  
 !     control the rate of approach to quasi-equilibrium)  
 !     (common cvparam)  
   
       if (iflag_con.eq.3) then  
        CALL cv3_param(nd,delt)  
       endif  
2    
3        if (iflag_con.eq.4) then    implicit none
4         CALL cv_param(nd)  
5        endif  contains
6    
7  !---------------------------------------------------------------------    SUBROUTINE cv_driver(len, nd, ndp1, ntra, iflag_con, t1, q1, qs1, u1, v1, &
8  ! --- INITIALIZE OUTPUT ARRAYS AND PARAMETERS         tra1, p1, ph1, iflag1, ft1, fq1, fu1, fv1, ftra1, precip1, VPrecip1, &
9  !---------------------------------------------------------------------         cbmf1, sig1, w01, icb1, inb1, delt, Ma1, upwd1, dnwd1, dnwd01, &
10           qcondc1, wd1, cape1, da1, phi1, mp1)
11        do 20 k=1,nd  
12          do 10 i=1,len      ! From LMDZ4/libf/phylmd/cv_driver.F, version 1.3 2005/04/15 12:36:17
13           ft1(i,k)=0.0  
14           fq1(i,k)=0.0      USE dimphy, ONLY: klev, klon
15           fu1(i,k)=0.0  
16           fv1(i,k)=0.0      ! PARAMETERS:
17           tvp1(i,k)=0.0      !      Name            Type         Usage            Description
18           tp1(i,k)=0.0      !   ----------      ----------     -------  ----------------------------
19           clw1(i,k)=0.0  
20  !ym      !      len           Integer        Input        first (i) dimension
21           clw(i,k)=0.0      !      nd            Integer        Input        vertical (k) dimension
22           gz1(i,k) = 0.      !      ndp1          Integer        Input        nd + 1
23           VPrecip1(i,k) = 0.      !      ntra          Integer        Input        number of tracors
24           Ma1(i,k)=0.0      !      iflag_con     Integer        Input        version of convect (3/4)
25           upwd1(i,k)=0.0      !      t1            Real           Input        temperature
26           dnwd1(i,k)=0.0      !      q1            Real           Input        specific hum
27           dnwd01(i,k)=0.0      !      qs1           Real           Input        sat specific hum
28           qcondc1(i,k)=0.0      !      u1            Real           Input        u-wind
29   10     continue      !      v1            Real           Input        v-wind
30   20   continue      !      tra1          Real           Input        tracors
31        !      p1            Real           Input        full level pressure
32        do 30 j=1,ntra      !      ph1           Real           Input        half level pressure
33         do 31 k=1,nd      !      iflag1        Integer        Output       flag for Emanuel conditions
34          do 32 i=1,len      !      ft1           Real           Output       temp tend
35           ftra1(i,k,j)=0.0      !      fq1           Real           Output       spec hum tend
36   32     continue      !      fu1           Real           Output       u-wind tend
37   31    continue      !      fv1           Real           Output       v-wind tend
38   30   continue      !      ftra1         Real           Output       tracor tend
39        !      precip1       Real           Output       precipitation
40        do 60 i=1,len      !      VPrecip1      Real           Output       vertical profile of precipitations
41          precip1(i)=0.0      !      cbmf1         Real           Output       cloud base mass flux
42          iflag1(i)=0      !      sig1          Real           In/Out       section adiabatic updraft
43          wd1(i)=0.0      !      w01           Real           In/Out       vertical velocity within adiab updraft
44          cape1(i)=0.0      !      delt          Real           Input        time step
45          VPrecip1(i,nd+1)=0.0      !      Ma1           Real           Output       mass flux adiabatic updraft
46   60   continue      !      qcondc1       Real           Output       in-cld mixing ratio of condensed water
47        !      wd1           Real           Output       downdraft velocity scale for sfc fluxes
48        if (iflag_con.eq.3) then      !      cape1         Real           Output       CAPE
49          do il=1,len  
50           sig1(il,nd)=sig1(il,nd)+1.      ! S. Bony, Mar 2002:
51           sig1(il,nd)=amin1(sig1(il,nd),12.1)      !     * Several modules corresponding to different physical processes
52          enddo      !     * Several versions of convect may be used:
53        endif      !        - iflag_con=3: version lmd  (previously named convect3)
54        !        - iflag_con=4: version 4.3b (vect. version, previously convect1/2)
55  !--------------------------------------------------------------------      !   + tard:    - iflag_con=5: version lmd with ice (previously named convectg)
56  ! --- CALCULATE ARRAYS OF GEOPOTENTIAL, HEAT CAPACITY & STATIC ENERGY      ! S. Bony, Oct 2002:
57  !--------------------------------------------------------------------      !     * Vectorization of convect3 (ie version lmd)
58    
59        if (iflag_con.eq.3) then      integer len
60         CALL cv3_prelim(len,nd,ndp1,t1,q1,p1,ph1             &      integer nd
61                       ,lv1,cpn1,tv1,gz1,h1,hm1,th1)! nd->na      integer ndp1
62        endif      integer noff
63        integer, intent(in):: iflag_con
64        if (iflag_con.eq.4) then      integer ntra
65         CALL cv_prelim(len,nd,ndp1,t1,q1,p1,ph1 &      real, intent(in):: t1(len, nd)
66                       ,lv1,cpn1,tv1,gz1,h1,hm1)      real q1(len, nd)
67        endif      real qs1(len, nd)
68        real u1(len, nd)
69  !--------------------------------------------------------------------      real v1(len, nd)
70  ! --- CONVECTIVE FEED      real p1(len, nd)
71  !--------------------------------------------------------------------      real ph1(len, ndp1)
72        integer iflag1(len)
73        if (iflag_con.eq.3) then      real ft1(len, nd)
74         CALL cv3_feed(len,nd,t1,q1,qs1,p1,ph1,hm1,gz1            &      real fq1(len, nd)
75                 ,nk1,icb1,icbmax,iflag1,tnk1,qnk1,gznk1,plcl1) ! nd->na      real fu1(len, nd)
76        endif      real fv1(len, nd)
77        real precip1(len)
78        if (iflag_con.eq.4) then      real cbmf1(len)
79         CALL cv_feed(len,nd,t1,q1,qs1,p1,hm1,gz1 &      real VPrecip1(len, nd+1)
80                 ,nk1,icb1,icbmax,iflag1,tnk1,qnk1,gznk1,plcl1)      real Ma1(len, nd)
81        endif      real, intent(out):: upwd1(len, nd) ! total upward mass flux (adiab+mixed)
82        real, intent(out):: dnwd1(len, nd) ! saturated downward mass flux (mixed)
83  !--------------------------------------------------------------------      real, intent(out):: dnwd01(len, nd) ! unsaturated downward mass flux
84  ! --- UNDILUTE (ADIABATIC) UPDRAFT / 1st part  
85  ! (up through ICB for convect4, up through ICB+1 for convect3)      real qcondc1(len, nd)     ! cld
86  !     Calculates the lifted parcel virtual temperature at nk, the      real wd1(len)            ! gust
87  !     actual temperature, and the adiabatic liquid water content.      real cape1(len)
88  !--------------------------------------------------------------------  
89        real da1(len, nd), phi1(len, nd, nd), mp1(len, nd)
90        if (iflag_con.eq.3) then      real da(len, nd), phi(len, nd, nd), mp(len, nd)
91         CALL cv3_undilute1(len,nd,t1,q1,qs1,gz1,plcl1,p1,nk1,icb1   &      real, intent(in):: tra1(len, nd, ntra)
92                                ,tp1,tvp1,clw1,icbs1) ! nd->na      real ftra1(len, nd, ntra)
93        endif  
94        real, intent(in):: delt
95        if (iflag_con.eq.4) then  
96         CALL cv_undilute1(len,nd,t1,q1,qs1,gz1,p1,nk1,icb1,icbmax &      !-------------------------------------------------------------------
97                                ,tp1,tvp1,clw1)      ! --- ARGUMENTS
98        endif      !-------------------------------------------------------------------
99        ! --- On input:
100  !-------------------------------------------------------------------  
101  ! --- TRIGGERING      !  t:   Array of absolute temperature (K) of dimension ND, with first
102  !-------------------------------------------------------------------      !       index corresponding to lowest model level. Note that this array
103        !       will be altered by the subroutine if dry convective adjustment
104        if (iflag_con.eq.3) then      !       occurs and if IPBL is not equal to 0.
105         CALL cv3_trigger(len,nd,icb1,plcl1,p1,th1,tv1,tvp1       &  
106                         ,pbase1,buoybase1,iflag1,sig1,w01) ! nd->na      !  q:   Array of specific humidity (gm/gm) of dimension ND, with first
107        endif      !       index corresponding to lowest model level. Must be defined
108        !       at same grid levels as T. Note that this array will be altered
109        if (iflag_con.eq.4) then      !       if dry convective adjustment occurs and if IPBL is not equal to 0.
110         CALL cv_trigger(len,nd,icb1,cbmf1,tv1,tvp1,iflag1)  
111        endif      !  qs:  Array of saturation specific humidity of dimension ND, with first
112        !       index corresponding to lowest model level. Must be defined
113  !=====================================================================      !       at same grid levels as T. Note that this array will be altered
114  ! --- IF THIS POINT IS REACHED, MOIST CONVECTIVE ADJUSTMENT IS NECESSARY      !       if dry convective adjustment occurs and if IPBL is not equal to 0.
115  !=====================================================================  
116        !  u:   Array of zonal wind velocity (m/s) of dimension ND, witth first
117        ncum=0      !       index corresponding with the lowest model level. Defined at
118        do 400 i=1,len      !       same levels as T. Note that this array will be altered if
119          if(iflag1(i).eq.0)then      !       dry convective adjustment occurs and if IPBL is not equal to 0.
120             ncum=ncum+1  
121             idcum(ncum)=i      !  v:   Same as u but for meridional velocity.
122          endif  
123   400  continue      !  tra: Array of passive tracer mixing ratio, of dimensions (ND, NTRA),
124        !       where NTRA is the number of different tracers. If no
125  !       print*,'klon, ncum = ',len,ncum      !       convective tracer transport is needed, define a dummy
126        !       input array of dimension (ND, 1). Tracers are defined at
127        IF (ncum.gt.0) THEN      !       same vertical levels as T. Note that this array will be altered
128        !       if dry convective adjustment occurs and if IPBL is not equal to 0.
129  !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^  
130  ! --- COMPRESS THE FIELDS      !  p:   Array of pressure (mb) of dimension ND, with first
131  !        (-> vectorization over convective gridpoints)      !       index corresponding to lowest model level. Must be defined
132  !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^      !       at same grid levels as T.
133    
134        if (iflag_con.eq.3) then      !  ph:  Array of pressure (mb) of dimension ND+1, with first index
135         CALL cv3_compress( len,nloc,ncum,nd,ntra &      !       corresponding to lowest level. These pressures are defined at
136            ,iflag1,nk1,icb1,icbs1 &      !       levels intermediate between those of P, T, Q and QS. The first
137            ,plcl1,tnk1,qnk1,gznk1,pbase1,buoybase1 &      !       value of PH should be greater than (i.e. at a lower level than)
138            ,t1,q1,qs1,u1,v1,gz1,th1 &      !       the first value of the array P.
139            ,tra1 &  
140            ,h1,lv1,cpn1,p1,ph1,tv1,tp1,tvp1,clw1  &      !  nl:  The maximum number of levels to which convection can penetrate, plus 1.
141            ,sig1,w01 &      !       NL MUST be less than or equal to ND-1.
142            ,iflag,nk,icb,icbs &  
143            ,plcl,tnk,qnk,gznk,pbase,buoybase &      !  delt: The model time step (sec) between calls to CONVECT
144            ,t,q,qs,u,v,gz,th &  
145            ,tra &      !----------------------------------------------------------------------------
146            ,h,lv,cpn,p,ph,tv,tp,tvp,clw  &      ! ---   On Output:
147            ,sig,w0  )  
148        endif      !  iflag: An output integer whose value denotes the following:
149        !       VALUE   INTERPRETATION
150        if (iflag_con.eq.4) then      !       -----   --------------
151         CALL cv_compress( len,nloc,ncum,nd &      !         0     Moist convection occurs.
152            ,iflag1,nk1,icb1 &      !         1     Moist convection occurs, but a CFL condition
153            ,cbmf1,plcl1,tnk1,qnk1,gznk1 &      !               on the subsidence warming is violated. This
154            ,t1,q1,qs1,u1,v1,gz1 &      !               does not cause the scheme to terminate.
155            ,h1,lv1,cpn1,p1,ph1,tv1,tp1,tvp1,clw1 &      !         2     Moist convection, but no precip because ep(inb) lt 0.0001
156            ,iflag,nk,icb &      !         3     No moist convection because new cbmf is 0 and old cbmf is 0.
157            ,cbmf,plcl,tnk,qnk,gznk &      !         4     No moist convection; atmosphere is not
158            ,t,q,qs,u,v,gz,h,lv,cpn,p,ph,tv,tp,tvp,clw  &      !               unstable
159            ,dph )      !         6     No moist convection because ihmin le minorig.
160        endif      !         7     No moist convection because unreasonable
161        !               parcel level temperature or specific humidity.
162  !-------------------------------------------------------------------      !         8     No moist convection: lifted condensation
163  ! --- UNDILUTE (ADIABATIC) UPDRAFT / second part :      !               level is above the 200 mb level.
164  ! ---   FIND THE REST OF THE LIFTED PARCEL TEMPERATURES      !         9     No moist convection: cloud base is higher
165  ! ---   &      !               then the level NL-1.
166  ! ---   COMPUTE THE PRECIPITATION EFFICIENCIES AND THE  
167  ! ---   FRACTION OF PRECIPITATION FALLING OUTSIDE OF CLOUD      !  ft:   Array of temperature tendency (K/s) of dimension ND, defined at same
168  ! ---   &      !        grid levels as T, Q, QS and P.
169  ! ---   FIND THE LEVEL OF NEUTRAL BUOYANCY  
170  !-------------------------------------------------------------------      !  fq:   Array of specific humidity tendencies ((gm/gm)/s) of dimension ND,
171        !        defined at same grid levels as T, Q, QS and P.
172        if (iflag_con.eq.3) then  
173         CALL cv3_undilute2(nloc,ncum,nd,icb,icbs,nk         &      !  fu:   Array of forcing of zonal velocity (m/s^2) of dimension ND,
174                                ,tnk,qnk,gznk,t,q,qs,gz &      !        defined at same grid levels as T.
175                                ,p,h,tv,lv,pbase,buoybase,plcl &  
176                                ,inb,tp,tvp,clw,hp,ep,sigp,buoy) !na->nd      !  fv:   Same as FU, but for forcing of meridional velocity.
177        endif  
178        !  ftra: Array of forcing of tracer content, in tracer mixing ratio per
179        if (iflag_con.eq.4) then      !        second, defined at same levels as T. Dimensioned (ND, NTRA).
180         CALL cv_undilute2(nloc,ncum,nd,icb,nk &  
181                                ,tnk,qnk,gznk,t,q,qs,gz &      !  precip: Scalar convective precipitation rate (mm/day).
182                                ,p,dph,h,tv,lv &  
183                     ,inb,inbis,tp,tvp,clw,hp,ep,sigp,frac)      !  VPrecip: Vertical profile of convective precipitation (kg/m2/s).
184        endif  
185        !  wd:   A convective downdraft velocity scale. For use in surface
186  !-------------------------------------------------------------------      !        flux parameterizations. See convect.ps file for details.
187  ! --- CLOSURE  
188  !-------------------------------------------------------------------      !  tprime: A convective downdraft temperature perturbation scale (K).
189        !          For use in surface flux parameterizations. See convect.ps
190        if (iflag_con.eq.3) then      !          file for details.
191         CALL cv3_closure(nloc,ncum,nd,icb,inb               &  
192                               ,pbase,p,ph,tv,buoy &      !  qprime: A convective downdraft specific humidity
193                               ,sig,w0,cape,m) ! na->nd      !          perturbation scale (gm/gm).
194        endif      !          For use in surface flux parameterizations. See convect.ps
195        !          file for details.
196        if (iflag_con.eq.4) then  
197         CALL cv_closure(nloc,ncum,nd,nk,icb &      !  cbmf: The cloud base mass flux ((kg/m**2)/s). THIS SCALAR VALUE MUST
198                        ,tv,tvp,p,ph,dph,plcl,cpn &      !        BE STORED BY THE CALLING PROGRAM AND RETURNED TO CONVECT AT
199                        ,iflag,cbmf)      !        ITS NEXT CALL. That is, the value of CBMF must be "remembered"
200        endif      !        by the calling program between calls to CONVECT.
201    
202  !-------------------------------------------------------------------      !  det:   Array of detrainment mass flux of dimension ND.
203  ! --- MIXING  
204  !-------------------------------------------------------------------      !-------------------------------------------------------------------
205    
206        if (iflag_con.eq.3) then      !  Local arrays
207         CALL cv3_mixing(nloc,ncum,nd,nd,ntra,icb,nk,inb     &  
208                             ,ph,t,q,qs,u,v,tra,h,lv,qnk &      integer i, k, n, il, j
209                             ,hp,tv,tvp,ep,clw,m,sig &      integer icbmax
210         ,ment,qent,uent,vent, nent,sij,elij,ments,qents,traent)! na->nd      integer nk1(klon)
211        endif      integer icb1(klon)
212        integer inb1(klon)
213        if (iflag_con.eq.4) then      integer icbs1(klon)
214         CALL cv_mixing(nloc,ncum,nd,icb,nk,inb,inbis &  
215                             ,ph,t,q,qs,u,v,h,lv,qnk &      real plcl1(klon)
216                             ,hp,tv,tvp,ep,clw,cbmf &      real tnk1(klon)
217                             ,m,ment,qent,uent,vent,nent,sij,elij)      real qnk1(klon)
218        endif      real gznk1(klon)
219        real pnk1(klon)
220  !-------------------------------------------------------------------      real qsnk1(klon)
221  ! --- UNSATURATED (PRECIPITATING) DOWNDRAFTS      real pbase1(klon)
222  !-------------------------------------------------------------------      real buoybase1(klon)
223    
224        if (iflag_con.eq.3) then      real lv1(klon, klev)
225         CALL cv3_unsat(nloc,ncum,nd,nd,ntra,icb,inb     &      real cpn1(klon, klev)
226                       ,t,q,qs,gz,u,v,tra,p,ph &      real tv1(klon, klev)
227                       ,th,tv,lv,cpn,ep,sigp,clw &      real gz1(klon, klev)
228                       ,m,ment,elij,delt,plcl &      real hm1(klon, klev)
229                  ,mp,qp,up,vp,trap,wt,water,evap,b)! na->nd      real h1(klon, klev)
230        endif      real tp1(klon, klev)
231        real tvp1(klon, klev)
232        if (iflag_con.eq.4) then      real clw1(klon, klev)
233         CALL cv_unsat(nloc,ncum,nd,inb,t,q,qs,gz,u,v,p,ph &      real sig1(klon, klev)
234                           ,h,lv,ep,sigp,clw,m,ment,elij &      real w01(klon, klev)
235                           ,iflag,mp,qp,up,vp,wt,water,evap)      real th1(klon, klev)
236        endif  
237        integer ncum
238  !-------------------------------------------------------------------  
239  ! --- YIELD      ! (local) compressed fields:
240  !     (tendencies, precipitation, variables of interface with other  
241  !      processes, etc)      integer nloc
242  !-------------------------------------------------------------------      parameter (nloc=klon) ! pour l'instant
243    
244        if (iflag_con.eq.3) then      integer idcum(nloc)
245         CALL cv3_yield(nloc,ncum,nd,nd,ntra             &      integer iflag(nloc), nk(nloc), icb(nloc)
246                             ,icb,inb,delt &      integer nent(nloc, klev)
247                             ,t,q,u,v,tra,gz,p,ph,h,hp,lv,cpn,th &      integer icbs(nloc)
248                             ,ep,clw,m,tp,mp,qp,up,vp,trap &      integer inb(nloc), inbis(nloc)
249                             ,wt,water,evap,b &  
250                             ,ment,qent,uent,vent,nent,elij,traent,sig &      real cbmf(nloc), plcl(nloc), tnk(nloc), qnk(nloc), gznk(nloc)
251                             ,tv,tvp &      real t(nloc, klev), q(nloc, klev), qs(nloc, klev)
252                             ,iflag,precip,VPrecip,ft,fq,fu,fv,ftra &      real u(nloc, klev), v(nloc, klev)
253                             ,upwd,dnwd,dnwd0,ma,mike,tls,tps,qcondc,wd)! na->nd      real gz(nloc, klev), h(nloc, klev), lv(nloc, klev), cpn(nloc, klev)
254        endif      real p(nloc, klev), ph(nloc, klev+1), tv(nloc, klev), tp(nloc, klev)
255        real clw(nloc, klev)
256        if (iflag_con.eq.4) then      real dph(nloc, klev)
257         CALL cv_yield(nloc,ncum,nd,nk,icb,inb,delt &      real pbase(nloc), buoybase(nloc), th(nloc, klev)
258                      ,t,q,u,v,gz,p,ph,h,hp,lv,cpn &      real tvp(nloc, klev)
259                      ,ep,clw,frac,m,mp,qp,up,vp &      real sig(nloc, klev), w0(nloc, klev)
260                      ,wt,water,evap &      real hp(nloc, klev), ep(nloc, klev), sigp(nloc, klev)
261                      ,ment,qent,uent,vent,nent,elij &      real frac(nloc), buoy(nloc, klev)
262                      ,tv,tvp &      real cape(nloc)
263                      ,iflag,wd,qprime,tprime &      real m(nloc, klev), ment(nloc, klev, klev), qent(nloc, klev, klev)
264                      ,precip,cbmf,ft,fq,fu,fv,Ma,qcondc)      real uent(nloc, klev, klev), vent(nloc, klev, klev)
265        endif      real ments(nloc, klev, klev), qents(nloc, klev, klev)
266        real sij(nloc, klev, klev), elij(nloc, klev, klev)
267  !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^      real qp(nloc, klev), up(nloc, klev), vp(nloc, klev)
268  ! --- passive tracers      real wt(nloc, klev), water(nloc, klev), evap(nloc, klev)
269  !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^      real b(nloc, klev), ft(nloc, klev), fq(nloc, klev)
270        real fu(nloc, klev), fv(nloc, klev)
271        if (iflag_con.eq.3) then      real upwd(nloc, klev), dnwd(nloc, klev), dnwd0(nloc, klev)
272         CALL cv3_tracer(nloc,len,ncum,nd,nd, &      real Ma(nloc, klev), mike(nloc, klev), tls(nloc, klev)
273                          ment,sij,da,phi)      real tps(nloc, klev), qprime(nloc), tprime(nloc)
274        endif      real precip(nloc)
275        real VPrecip(nloc, klev+1)
276  !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^      real tra(nloc, klev, ntra), trap(nloc, klev, ntra)
277  ! --- UNCOMPRESS THE FIELDS      real ftra(nloc, klev, ntra), traent(nloc, klev, klev, ntra)
278  !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^      real qcondc(nloc, klev)  ! cld
279  ! set iflag1 =42 for non convective points      real wd(nloc)           ! gust
280        do  i=1,len  
281          iflag1(i)=42      !-------------------------------------------------------------------
282        end do      ! --- SET CONSTANTS AND PARAMETERS
283  !      !-------------------------------------------------------------------
284        if (iflag_con.eq.3) then  
285         CALL cv3_uncompress(nloc,len,ncum,nd,ntra,idcum &      ! -- set simulation flags:
286                  ,iflag &      !   (common cvflag)
287                  ,precip,VPrecip,sig,w0 &  
288                  ,ft,fq,fu,fv,ftra &      CALL cv_flag
289                  ,inb  &  
290                  ,Ma,upwd,dnwd,dnwd0,qcondc,wd,cape &      ! -- set thermodynamical constants:
291                  ,da,phi,mp &      !     (common cvthermo)
292                  ,iflag1 &  
293                  ,precip1,VPrecip1,sig1,w01 &      CALL cv_thermo(iflag_con)
294                  ,ft1,fq1,fu1,fv1,ftra1 &  
295                  ,inb1 &      ! -- set convect parameters
296                  ,Ma1,upwd1,dnwd1,dnwd01,qcondc1,wd1,cape1  &  
297                  ,da1,phi1,mp1)      !     includes microphysical parameters and parameters that
298        endif      !     control the rate of approach to quasi-equilibrium)
299        !     (common cvparam)
300        if (iflag_con.eq.4) then  
301         CALL cv_uncompress(nloc,len,ncum,nd,idcum &      if (iflag_con.eq.3) then
302                  ,iflag &         CALL cv3_param(nd, delt)
303                  ,precip,cbmf &      endif
304                  ,ft,fq,fu,fv &  
305                  ,Ma,qcondc             &      if (iflag_con.eq.4) then
306                  ,iflag1 &         CALL cv_param(nd)
307                  ,precip1,cbmf1 &      endif
                 ,ft1,fq1,fu1,fv1 &  
                 ,Ma1,qcondc1 )  
       endif  
308    
309        ENDIF ! ncum>0      !---------------------------------------------------------------------
310        ! --- INITIALIZE OUTPUT ARRAYS AND PARAMETERS
311        !---------------------------------------------------------------------
312    
313        do k=1, nd
314           do  i=1, len
315              ft1(i, k)=0.0
316              fq1(i, k)=0.0
317              fu1(i, k)=0.0
318              fv1(i, k)=0.0
319              tvp1(i, k)=0.0
320              tp1(i, k)=0.0
321              clw1(i, k)=0.0
322              !ym
323              clw(i, k)=0.0
324              gz1(i, k) = 0.
325              VPrecip1(i, k) = 0.
326              Ma1(i, k)=0.0
327              upwd1(i, k)=0.0
328              dnwd1(i, k)=0.0
329              dnwd01(i, k)=0.0
330              qcondc1(i, k)=0.0
331           end do
332        end do
333    
334        do  j=1, ntra
335           do  k=1, nd
336              do  i=1, len
337                 ftra1(i, k, j)=0.0
338              end do
339           end do
340        end do
341    
342        do  i=1, len
343           precip1(i)=0.0
344           iflag1(i)=0
345           wd1(i)=0.0
346           cape1(i)=0.0
347           VPrecip1(i, nd+1)=0.0
348        end do
349    
350        if (iflag_con.eq.3) then
351           do il=1, len
352              sig1(il, nd)=sig1(il, nd)+1.
353              sig1(il, nd)=amin1(sig1(il, nd), 12.1)
354           enddo
355        endif
356    
357        !--------------------------------------------------------------------
358        ! --- CALCULATE ARRAYS OF GEOPOTENTIAL, HEAT CAPACITY & STATIC ENERGY
359        !--------------------------------------------------------------------
360    
361        if (iflag_con.eq.3) then
362           CALL cv3_prelim(len, nd, ndp1, t1, q1, p1, ph1, lv1, cpn1, tv1, gz1, &
363                h1, hm1, th1)! nd->na
364        endif
365    
366        if (iflag_con.eq.4) then
367           CALL cv_prelim(len, nd, ndp1, t1, q1, p1, ph1 &
368                , lv1, cpn1, tv1, gz1, h1, hm1)
369        endif
370    
371        !--------------------------------------------------------------------
372        ! --- CONVECTIVE FEED
373        !--------------------------------------------------------------------
374    
375        if (iflag_con.eq.3) then
376           CALL cv3_feed(len, nd, t1, q1, qs1, p1, ph1, hm1, gz1            &
377                , nk1, icb1, icbmax, iflag1, tnk1, qnk1, gznk1, plcl1) ! nd->na
378        endif
379    
380        if (iflag_con.eq.4) then
381           CALL cv_feed(len, nd, t1, q1, qs1, p1, hm1, gz1 &
382                , nk1, icb1, icbmax, iflag1, tnk1, qnk1, gznk1, plcl1)
383        endif
384    
385        !--------------------------------------------------------------------
386        ! --- UNDILUTE (ADIABATIC) UPDRAFT / 1st part
387        ! (up through ICB for convect4, up through ICB+1 for convect3)
388        !     Calculates the lifted parcel virtual temperature at nk, the
389        !     actual temperature, and the adiabatic liquid water content.
390        !--------------------------------------------------------------------
391    
392        if (iflag_con.eq.3) then
393           CALL cv3_undilute1(len, nd, t1, q1, qs1, gz1, plcl1, p1, nk1, icb1   &
394                , tp1, tvp1, clw1, icbs1) ! nd->na
395        endif
396    
397        if (iflag_con.eq.4) then
398           CALL cv_undilute1(len, nd, t1, q1, qs1, gz1, p1, nk1, icb1, icbmax &
399                , tp1, tvp1, clw1)
400        endif
401    
402        !-------------------------------------------------------------------
403        ! --- TRIGGERING
404        !-------------------------------------------------------------------
405    
406        if (iflag_con.eq.3) then
407           CALL cv3_trigger(len, nd, icb1, plcl1, p1, th1, tv1, tvp1       &
408                , pbase1, buoybase1, iflag1, sig1, w01) ! nd->na
409        endif
410    
411        if (iflag_con.eq.4) then
412           CALL cv_trigger(len, nd, icb1, cbmf1, tv1, tvp1, iflag1)
413        endif
414    
415        !=====================================================================
416        ! --- IF THIS POINT IS REACHED, MOIST CONVECTIVE ADJUSTMENT IS NECESSARY
417        !=====================================================================
418    
419        ncum=0
420        do  i=1, len
421           if(iflag1(i).eq.0)then
422              ncum=ncum+1
423              idcum(ncum)=i
424           endif
425        end do
426    
427        !       print*, 'klon, ncum = ', len, ncum
428    
429        IF (ncum.gt.0) THEN
430    
431           !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
432           ! --- COMPRESS THE FIELDS
433           !        (-> vectorization over convective gridpoints)
434           !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
435    
436           if (iflag_con.eq.3) then
437              CALL cv3_compress( len, nloc, ncum, nd, ntra &
438                   , iflag1, nk1, icb1, icbs1 &
439                   , plcl1, tnk1, qnk1, gznk1, pbase1, buoybase1 &
440                   , t1, q1, qs1, u1, v1, gz1, th1 &
441                   , tra1 &
442                   , h1, lv1, cpn1, p1, ph1, tv1, tp1, tvp1, clw1  &
443                   , sig1, w01 &
444                   , iflag, nk, icb, icbs &
445                   , plcl, tnk, qnk, gznk, pbase, buoybase &
446                   , t, q, qs, u, v, gz, th &
447                   , tra &
448                   , h, lv, cpn, p, ph, tv, tp, tvp, clw  &
449                   , sig, w0  )
450           endif
451    
452           if (iflag_con.eq.4) then
453              CALL cv_compress( len, nloc, ncum, nd &
454                   , iflag1, nk1, icb1 &
455                   , cbmf1, plcl1, tnk1, qnk1, gznk1 &
456                   , t1, q1, qs1, u1, v1, gz1 &
457                   , h1, lv1, cpn1, p1, ph1, tv1, tp1, tvp1, clw1 &
458                   , iflag, nk, icb &
459                   , cbmf, plcl, tnk, qnk, gznk &
460                   , t, q, qs, u, v, gz, h, lv, cpn, p, ph, tv, tp, tvp, clw  &
461                   , dph )
462           endif
463    
464           !-------------------------------------------------------------------
465           ! --- UNDILUTE (ADIABATIC) UPDRAFT / second part :
466           ! ---   FIND THE REST OF THE LIFTED PARCEL TEMPERATURES
467           ! ---   &
468           ! ---   COMPUTE THE PRECIPITATION EFFICIENCIES AND THE
469           ! ---   FRACTION OF PRECIPITATION FALLING OUTSIDE OF CLOUD
470           ! ---   &
471           ! ---   FIND THE LEVEL OF NEUTRAL BUOYANCY
472           !-------------------------------------------------------------------
473    
474           if (iflag_con.eq.3) then
475              CALL cv3_undilute2(nloc, ncum, nd, icb, icbs, nk         &
476                   , tnk, qnk, gznk, t, q, qs, gz &
477                   , p, h, tv, lv, pbase, buoybase, plcl &
478                   , inb, tp, tvp, clw, hp, ep, sigp, buoy) !na->nd
479           endif
480    
481           if (iflag_con.eq.4) then
482              CALL cv_undilute2(nloc, ncum, nd, icb, nk &
483                   , tnk, qnk, gznk, t, q, qs, gz &
484                   , p, dph, h, tv, lv &
485                   , inb, inbis, tp, tvp, clw, hp, ep, sigp, frac)
486           endif
487    
488           !-------------------------------------------------------------------
489           ! --- CLOSURE
490           !-------------------------------------------------------------------
491    
492           if (iflag_con.eq.3) then
493              CALL cv3_closure(nloc, ncum, nd, icb, inb               &
494                   , pbase, p, ph, tv, buoy &
495                   , sig, w0, cape, m) ! na->nd
496           endif
497    
498           if (iflag_con.eq.4) then
499              CALL cv_closure(nloc, ncum, nd, nk, icb &
500                   , tv, tvp, p, ph, dph, plcl, cpn &
501                   , iflag, cbmf)
502           endif
503    
504           !-------------------------------------------------------------------
505           ! --- MIXING
506           !-------------------------------------------------------------------
507    
508           if (iflag_con.eq.3) then
509              CALL cv3_mixing(nloc, ncum, nd, nd, ntra, icb, nk, inb     &
510                   , ph, t, q, qs, u, v, tra, h, lv, qnk &
511                   , hp, tv, tvp, ep, clw, m, sig &
512                   , ment, qent, uent, vent, nent, sij, elij, ments, qents, traent)! na->nd
513           endif
514    
515           if (iflag_con.eq.4) then
516              CALL cv_mixing(nloc, ncum, nd, icb, nk, inb, inbis &
517                   , ph, t, q, qs, u, v, h, lv, qnk &
518                   , hp, tv, tvp, ep, clw, cbmf &
519                   , m, ment, qent, uent, vent, nent, sij, elij)
520           endif
521    
522           !-------------------------------------------------------------------
523           ! --- UNSATURATED (PRECIPITATING) DOWNDRAFTS
524           !-------------------------------------------------------------------
525    
526           if (iflag_con.eq.3) then
527              CALL cv3_unsat(nloc, ncum, nd, nd, ntra, icb, inb     &
528                   , t, q, qs, gz, u, v, tra, p, ph &
529                   , th, tv, lv, cpn, ep, sigp, clw &
530                   , m, ment, elij, delt, plcl &
531                   , mp, qp, up, vp, trap, wt, water, evap, b)! na->nd
532           endif
533    
534           if (iflag_con.eq.4) then
535              CALL cv_unsat(nloc, ncum, nd, inb, t, q, qs, gz, u, v, p, ph &
536                   , h, lv, ep, sigp, clw, m, ment, elij &
537                   , iflag, mp, qp, up, vp, wt, water, evap)
538           endif
539    
540           !-------------------------------------------------------------------
541           ! --- YIELD
542           !     (tendencies, precipitation, variables of interface with other
543           !      processes, etc)
544           !-------------------------------------------------------------------
545    
546           if (iflag_con.eq.3) then
547              CALL cv3_yield(nloc, ncum, nd, nd, ntra             &
548                   , icb, inb, delt &
549                   , t, q, u, v, tra, gz, p, ph, h, hp, lv, cpn, th &
550                   , ep, clw, m, tp, mp, qp, up, vp, trap &
551                   , wt, water, evap, b &
552                   , ment, qent, uent, vent, nent, elij, traent, sig &
553                   , tv, tvp &
554                   , iflag, precip, VPrecip, ft, fq, fu, fv, ftra &
555                   , upwd, dnwd, dnwd0, ma, mike, tls, tps, qcondc, wd)! na->nd
556           endif
557    
558           if (iflag_con.eq.4) then
559              CALL cv_yield(nloc, ncum, nd, nk, icb, inb, delt &
560                   , t, q, u, v, gz, p, ph, h, hp, lv, cpn &
561                   , ep, clw, frac, m, mp, qp, up, vp &
562                   , wt, water, evap &
563                   , ment, qent, uent, vent, nent, elij &
564                   , tv, tvp &
565                   , iflag, wd, qprime, tprime &
566                   , precip, cbmf, ft, fq, fu, fv, Ma, qcondc)
567           endif
568    
569           !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
570           ! --- passive tracers
571           !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
572    
573           if (iflag_con.eq.3) then
574              CALL cv3_tracer(nloc, len, ncum, nd, nd, &
575                   ment, sij, da, phi)
576           endif
577    
578           !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
579           ! --- UNCOMPRESS THE FIELDS
580           !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
581           ! set iflag1 =42 for non convective points
582           do  i=1, len
583              iflag1(i)=42
584           end do
585    
586           if (iflag_con.eq.3) then
587              CALL cv3_uncompress(nloc, len, ncum, nd, ntra, idcum &
588                   , iflag &
589                   , precip, VPrecip, sig, w0 &
590                   , ft, fq, fu, fv, ftra &
591                   , inb  &
592                   , Ma, upwd, dnwd, dnwd0, qcondc, wd, cape &
593                   , da, phi, mp &
594                   , iflag1 &
595                   , precip1, VPrecip1, sig1, w01 &
596                   , ft1, fq1, fu1, fv1, ftra1 &
597                   , inb1 &
598                   , Ma1, upwd1, dnwd1, dnwd01, qcondc1, wd1, cape1  &
599                   , da1, phi1, mp1)
600           endif
601    
602           if (iflag_con.eq.4) then
603              CALL cv_uncompress(nloc, len, ncum, nd, idcum &
604                   , iflag &
605                   , precip, cbmf &
606                   , ft, fq, fu, fv &
607                   , Ma, qcondc             &
608                   , iflag1 &
609                   , precip1, cbmf1 &
610                   , ft1, fq1, fu1, fv1 &
611                   , Ma1, qcondc1 )
612           endif
613        ENDIF ! ncum>0
614    
615  9999  continue    end SUBROUTINE cv_driver
616    
617        return  end module cv_driver_m
       end  

Legend:
Removed from v.49  
changed lines
  Added in v.62

  ViewVC Help
Powered by ViewVC 1.1.21