/[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

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

  ViewVC Help
Powered by ViewVC 1.1.21