/[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 52 by guez, Fri Sep 23 12:28:01 2011 UTC trunk/phylmd/cv_driver.f revision 97 by guez, Fri Apr 25 14:58:31 2014 UTC
# Line 4  module cv_driver_m Line 4  module cv_driver_m
4    
5  contains  contains
6    
7    SUBROUTINE cv_driver(len, nd, ndp1, ntra, iflag_con, t1, q1, qs1, u1, v1, &    SUBROUTINE cv_driver(len, nd, t1, q1, qs1, u1, v1, p1, ph1, iflag1, ft1, &
8         tra1, p1, ph1, iflag1, ft1, fq1, fu1, fv1, ftra1, precip1, VPrecip1, &         fq1, fu1, fv1, precip1, VPrecip1, cbmf1, sig1, w01, icb1, inb1, delt, &
9         cbmf1, sig1, w01, icb1, inb1, delt, Ma1, upwd1, dnwd1, dnwd01, &         Ma1, upwd1, dnwd1, dnwd01, qcondc1, wd1, cape1, da1, phi1, mp1)
10         qcondc1, wd1, cape1, da1, phi1, mp1)  
11        ! From LMDZ4/libf/phylmd/cv_driver.F, version 1.3, 2005/04/15 12:36:17
12      ! From LMDZ4/libf/phylmd/cv_driver.F, version 1.3 2005/04/15 12:36:17      ! Main driver for convection
13        ! Author: S. Bony, March 2002
14      use dimens_m  
15      use dimphy      ! Several modules corresponding to different physical processes
16      !  
17      ! PARAMETERS:      ! Several versions of convect may be used:
18      !      Name            Type         Usage            Description      ! - iflag_con = 3: version lmd
19      !   ----------      ----------     -------  ----------------------------      ! - iflag_con = 4: version 4.3b
20      !  
21      !      len           Integer        Input        first (i) dimension      use clesphys2, only: iflag_con
22      !      nd            Integer        Input        vertical (k) dimension      use cv3_compress_m, only: cv3_compress
23      !      ndp1          Integer        Input        nd + 1      use cv3_mixing_m, only: cv3_mixing
24      !      ntra          Integer        Input        number of tracors      use cv3_param_m, only: cv3_param
25      !      iflag_con     Integer        Input        version of convect (3/4)      use cv3_prelim_m, only: cv3_prelim
26      !      t1            Real           Input        temperature      use cv3_tracer_m, only: cv3_tracer
27      !      q1            Real           Input        specific hum      use cv3_uncompress_m, only: cv3_uncompress
28        use cv3_unsat_m, only: cv3_unsat
29        use cv3_yield_m, only: cv3_yield
30        use cv_uncompress_m, only: cv_uncompress
31        USE dimphy, ONLY: klev, klon
32    
33        integer, intent(in):: len ! first dimension
34        integer, intent(in):: nd ! vertical dimension
35        real, intent(in):: t1(len, nd) ! temperature
36        real q1(len, nd) !           Input        specific hum
37        real qs1(len, nd)
38      !      qs1           Real           Input        sat specific hum      !      qs1           Real           Input        sat specific hum
39        real, intent(in):: u1(len, nd)
40      !      u1            Real           Input        u-wind      !      u1            Real           Input        u-wind
41        real, intent(in):: v1(len, nd)
42      !      v1            Real           Input        v-wind      !      v1            Real           Input        v-wind
43      !      tra1          Real           Input        tracors      real p1(len, nd)
44      !      p1            Real           Input        full level pressure      !      p1            Real           Input        full level pressure
45        real ph1(len, nd + 1)
46      !      ph1           Real           Input        half level pressure      !      ph1           Real           Input        half level pressure
47        integer iflag1(len)
48      !      iflag1        Integer        Output       flag for Emanuel conditions      !      iflag1        Integer        Output       flag for Emanuel conditions
49        real ft1(len, nd)
50      !      ft1           Real           Output       temp tend      !      ft1           Real           Output       temp tend
51        real fq1(len, nd)
52      !      fq1           Real           Output       spec hum tend      !      fq1           Real           Output       spec hum tend
53        real fu1(len, nd)
54      !      fu1           Real           Output       u-wind tend      !      fu1           Real           Output       u-wind tend
55        real fv1(len, nd)
56      !      fv1           Real           Output       v-wind tend      !      fv1           Real           Output       v-wind tend
57      !      ftra1         Real           Output       tracor tend      real precip1(len)
58      !      precip1       Real           Output       precipitation      !      precip1       Real           Output       precipitation
59        real VPrecip1(len, nd+1)
60      !      VPrecip1      Real           Output       vertical profile of precipitations      !      VPrecip1      Real           Output       vertical profile of precipitations
61        real cbmf1(len)
62      !      cbmf1         Real           Output       cloud base mass flux      !      cbmf1         Real           Output       cloud base mass flux
63      !      sig1          Real           In/Out       section adiabatic updraft      real, intent(inout):: sig1(klon, klev) ! section adiabatic updraft
64      !      w01           Real           In/Out       vertical velocity within adiab updraft  
65        real, intent(inout):: w01(klon, klev)
66        ! vertical velocity within adiabatic updraft
67    
68        integer icb1(klon)
69        integer inb1(klon)
70        real, intent(in):: delt
71      !      delt          Real           Input        time step      !      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, intent(in):: 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)  
72      real Ma1(len, nd)      real Ma1(len, nd)
73      real upwd1(len, nd)      !      Ma1           Real           Output       mass flux adiabatic updraft
74      real dnwd1(len, nd)      real, intent(out):: upwd1(len, nd) ! total upward mass flux (adiab+mixed)
75      real dnwd01(len, nd)      real, intent(out):: dnwd1(len, nd) ! saturated downward mass flux (mixed)
76        real, intent(out):: dnwd01(len, nd) ! unsaturated downward mass flux
77    
78      real qcondc1(len, nd)     ! cld      real qcondc1(len, nd)     ! cld
79        !      qcondc1       Real           Output       in-cld mixing ratio of condensed water
80      real wd1(len)            ! gust      real wd1(len)            ! gust
81        !      wd1           Real           Output       downdraft velocity scale for sfc fluxes
82      real cape1(len)      real cape1(len)
83        !      cape1         Real           Output       CAPE
84    
85      real da1(len, nd), phi1(len, nd, nd), mp1(len, nd)      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  
86    
87      !-------------------------------------------------------------------      !-------------------------------------------------------------------
88      ! --- ARGUMENTS      ! --- ARGUMENTS
89      !-------------------------------------------------------------------      !-------------------------------------------------------------------
90      ! --- On input:      ! --- On input:
91      !  
92      !  t:   Array of absolute temperature (K) of dimension ND, with first      !  t:   Array of absolute temperature (K) of dimension ND, with first
93      !       index corresponding to lowest model level. Note that this array      !       index corresponding to lowest model level. Note that this array
94      !       will be altered by the subroutine if dry convective adjustment      !       will be altered by the subroutine if dry convective adjustment
95      !       occurs and if IPBL is not equal to 0.      !       occurs and if IPBL is not equal to 0.
96      !  
97      !  q:   Array of specific humidity (gm/gm) of dimension ND, with first      !  q:   Array of specific humidity (gm/gm) of dimension ND, with first
98      !       index corresponding to lowest model level. Must be defined      !       index corresponding to lowest model level. Must be defined
99      !       at same grid levels as T. Note that this array will be altered      !       at same grid levels as T. Note that this array will be altered
100      !       if dry convective adjustment occurs and if IPBL is not equal to 0.      !       if dry convective adjustment occurs and if IPBL is not equal to 0.
101      !  
102      !  qs:  Array of saturation specific humidity of dimension ND, with first      !  qs:  Array of saturation specific humidity of dimension ND, with first
103      !       index corresponding to lowest model level. Must be defined      !       index corresponding to lowest model level. Must be defined
104      !       at same grid levels as T. Note that this array will be altered      !       at same grid levels as T. Note that this array will be altered
105      !       if dry convective adjustment occurs and if IPBL is not equal to 0.      !       if dry convective adjustment occurs and if IPBL is not equal to 0.
106      !  
107      !  u:   Array of zonal wind velocity (m/s) of dimension ND, witth first      !  u:   Array of zonal wind velocity (m/s) of dimension ND, witth first
108      !       index corresponding with the lowest model level. Defined at      !       index corresponding with the lowest model level. Defined at
109      !       same levels as T. Note that this array will be altered if      !       same levels as T. Note that this array will be altered if
110      !       dry convective adjustment occurs and if IPBL is not equal to 0.      !       dry convective adjustment occurs and if IPBL is not equal to 0.
111      !  
112      !  v:   Same as u but for meridional velocity.      !  v:   Same as u but for meridional velocity.
113      !  
     !  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.  
     !  
114      !  p:   Array of pressure (mb) of dimension ND, with first      !  p:   Array of pressure (mb) of dimension ND, with first
115      !       index corresponding to lowest model level. Must be defined      !       index corresponding to lowest model level. Must be defined
116      !       at same grid levels as T.      !       at same grid levels as T.
117      !  
118      !  ph:  Array of pressure (mb) of dimension ND+1, with first index      !  ph:  Array of pressure (mb) of dimension ND+1, with first index
119      !       corresponding to lowest level. These pressures are defined at      !       corresponding to lowest level. These pressures are defined at
120      !       levels intermediate between those of P, T, Q and QS. The first      !       levels intermediate between those of P, T, Q and QS. The first
121      !       value of PH should be greater than (i.e. at a lower level than)      !       value of PH should be greater than (i.e. at a lower level than)
122      !       the first value of the array P.      !       the first value of the array P.
123      !  
124      !  nl:  The maximum number of levels to which convection can penetrate, plus 1.      !  nl:  The maximum number of levels to which convection can penetrate, plus 1.
125      !       NL MUST be less than or equal to ND-1.      !       NL MUST be less than or equal to ND-1.
126      !  
127      !  delt: The model time step (sec) between calls to CONVECT      !  delt: The model time step (sec) between calls to CONVECT
128      !  
129      !----------------------------------------------------------------------------      !----------------------------------------------------------------------------
130      ! ---   On Output:      ! ---   On Output:
131      !  
132      !  iflag: An output integer whose value denotes the following:      !  iflag: An output integer whose value denotes the following:
133      !       VALUE   INTERPRETATION      !       VALUE   INTERPRETATION
134      !       -----   --------------      !       -----   --------------
# Line 171  contains Line 147  contains
147      !               level is above the 200 mb level.      !               level is above the 200 mb level.
148      !         9     No moist convection: cloud base is higher      !         9     No moist convection: cloud base is higher
149      !               then the level NL-1.      !               then the level NL-1.
150      !  
151      !  ft:   Array of temperature tendency (K/s) of dimension ND, defined at same      !  ft:   Array of temperature tendency (K/s) of dimension ND, defined at same
152      !        grid levels as T, Q, QS and P.      !        grid levels as T, Q, QS and P.
153      !  
154      !  fq:   Array of specific humidity tendencies ((gm/gm)/s) of dimension ND,      !  fq:   Array of specific humidity tendencies ((gm/gm)/s) of dimension ND,
155      !        defined at same grid levels as T, Q, QS and P.      !        defined at same grid levels as T, Q, QS and P.
156      !  
157      !  fu:   Array of forcing of zonal velocity (m/s^2) of dimension ND,      !  fu:   Array of forcing of zonal velocity (m/s^2) of dimension ND,
158      !        defined at same grid levels as T.      !        defined at same grid levels as T.
159      !  
160      !  fv:   Same as FU, but for forcing of meridional velocity.      !  fv:   Same as FU, but for forcing of meridional velocity.
161      !  
     !  ftra: Array of forcing of tracer content, in tracer mixing ratio per  
     !        second, defined at same levels as T. Dimensioned (ND, NTRA).  
     !  
162      !  precip: Scalar convective precipitation rate (mm/day).      !  precip: Scalar convective precipitation rate (mm/day).
163      !  
164      !  VPrecip: Vertical profile of convective precipitation (kg/m2/s).      !  VPrecip: Vertical profile of convective precipitation (kg/m2/s).
165      !  
166      !  wd:   A convective downdraft velocity scale. For use in surface      !  wd:   A convective downdraft velocity scale. For use in surface
167      !        flux parameterizations. See convect.ps file for details.      !        flux parameterizations. See convect.ps file for details.
168      !  
169      !  tprime: A convective downdraft temperature perturbation scale (K).      !  tprime: A convective downdraft temperature perturbation scale (K).
170      !          For use in surface flux parameterizations. See convect.ps      !          For use in surface flux parameterizations. See convect.ps
171      !          file for details.      !          file for details.
172      !  
173      !  qprime: A convective downdraft specific humidity      !  qprime: A convective downdraft specific humidity
174      !          perturbation scale (gm/gm).      !          perturbation scale (gm/gm).
175      !          For use in surface flux parameterizations. See convect.ps      !          For use in surface flux parameterizations. See convect.ps
176      !          file for details.      !          file for details.
177      !  
178      !  cbmf: The cloud base mass flux ((kg/m**2)/s). THIS SCALAR VALUE MUST      !  cbmf: The cloud base mass flux ((kg/m**2)/s). THIS SCALAR VALUE MUST
179      !        BE STORED BY THE CALLING PROGRAM AND RETURNED TO CONVECT AT      !        BE STORED BY THE CALLING PROGRAM AND RETURNED TO CONVECT AT
180      !        ITS NEXT CALL. That is, the value of CBMF must be "remembered"      !        ITS NEXT CALL. That is, the value of CBMF must be "remembered"
181      !        by the calling program between calls to CONVECT.      !        by the calling program between calls to CONVECT.
182      !  
183      !  det:   Array of detrainment mass flux of dimension ND.      !  det:   Array of detrainment mass flux of dimension ND.
184      !  
185      !-------------------------------------------------------------------      !-------------------------------------------------------------------
186      !  
187      !  Local arrays      !  Local arrays
     !  
188    
189      integer i, k, n, il, j      real da(len, nd), phi(len, nd, nd), mp(len, nd)
190    
191        integer i, k, il
192      integer icbmax      integer icbmax
193      integer nk1(klon)      integer nk1(klon)
     integer icb1(klon)  
     integer inb1(klon)  
194      integer icbs1(klon)      integer icbs1(klon)
195    
196      real plcl1(klon)      real plcl1(klon)
197      real tnk1(klon)      real tnk1(klon)
198      real qnk1(klon)      real qnk1(klon)
199      real gznk1(klon)      real gznk1(klon)
     real pnk1(klon)  
     real qsnk1(klon)  
200      real pbase1(klon)      real pbase1(klon)
201      real buoybase1(klon)      real buoybase1(klon)
202    
# Line 239  contains Line 209  contains
209      real tp1(klon, klev)      real tp1(klon, klev)
210      real tvp1(klon, klev)      real tvp1(klon, klev)
211      real clw1(klon, klev)      real clw1(klon, klev)
     real sig1(klon, klev)  
     real w01(klon, klev)  
212      real th1(klon, klev)      real th1(klon, klev)
213      !  
214      integer ncum      integer ncum
215      !  
216      ! (local) compressed fields:      ! (local) compressed fields:
217      !  
218      integer nloc      integer nloc
219      parameter (nloc=klon) ! pour l'instant      parameter (nloc = klon) ! pour l'instant
220    
221      integer idcum(nloc)      integer idcum(nloc)
222      integer iflag(nloc), nk(nloc), icb(nloc)      integer iflag(nloc), nk(nloc), icb(nloc)
# Line 282  contains Line 250  contains
250      real tps(nloc, klev), qprime(nloc), tprime(nloc)      real tps(nloc, klev), qprime(nloc), tprime(nloc)
251      real precip(nloc)      real precip(nloc)
252      real VPrecip(nloc, klev+1)      real VPrecip(nloc, klev+1)
     real tra(nloc, klev, ntra), trap(nloc, klev, ntra)  
     real ftra(nloc, klev, ntra), traent(nloc, klev, klev, ntra)  
253      real qcondc(nloc, klev)  ! cld      real qcondc(nloc, klev)  ! cld
254      real wd(nloc)           ! gust      real wd(nloc)           ! gust
255    
# Line 299  contains Line 265  contains
265      ! -- set thermodynamical constants:      ! -- set thermodynamical constants:
266      !     (common cvthermo)      !     (common cvthermo)
267    
268      CALL cv_thermo(iflag_con)      CALL cv_thermo
269    
270      ! -- set convect parameters      ! -- set convect parameters
271      !  
272      !     includes microphysical parameters and parameters that      !     includes microphysical parameters and parameters that
273      !     control the rate of approach to quasi-equilibrium)      !     control the rate of approach to quasi-equilibrium)
274      !     (common cvparam)      !     (common cvparam)
# Line 319  contains Line 285  contains
285      ! --- INITIALIZE OUTPUT ARRAYS AND PARAMETERS      ! --- INITIALIZE OUTPUT ARRAYS AND PARAMETERS
286      !---------------------------------------------------------------------      !---------------------------------------------------------------------
287    
288      do k=1, nd      do k = 1, nd
289         do  i=1, len         do  i = 1, len
290            ft1(i, k)=0.0            ft1(i, k) = 0.0
291            fq1(i, k)=0.0            fq1(i, k) = 0.0
292            fu1(i, k)=0.0            fu1(i, k) = 0.0
293            fv1(i, k)=0.0            fv1(i, k) = 0.0
294            tvp1(i, k)=0.0            tvp1(i, k) = 0.0
295            tp1(i, k)=0.0            tp1(i, k) = 0.0
296            clw1(i, k)=0.0            clw1(i, k) = 0.0
297            !ym            !ym
298            clw(i, k)=0.0            clw(i, k) = 0.0
299            gz1(i, k) = 0.            gz1(i, k)  =  0.
300            VPrecip1(i, k) = 0.            VPrecip1(i, k) = 0.
301            Ma1(i, k)=0.0            Ma1(i, k) = 0.0
302            upwd1(i, k)=0.0            upwd1(i, k) = 0.0
303            dnwd1(i, k)=0.0            dnwd1(i, k) = 0.0
304            dnwd01(i, k)=0.0            dnwd01(i, k) = 0.0
305            qcondc1(i, k)=0.0            qcondc1(i, k) = 0.0
306         end do         end do
307      end do      end do
308    
309      do  j=1, ntra      do  i = 1, len
310         do  k=1, nd         precip1(i) = 0.0
311            do  i=1, len         iflag1(i) = 0
312               ftra1(i, k, j)=0.0         wd1(i) = 0.0
313            end do         cape1(i) = 0.0
314         end do         VPrecip1(i, nd+1) = 0.0
     end do  
   
     do  i=1, len  
        precip1(i)=0.0  
        iflag1(i)=0  
        wd1(i)=0.0  
        cape1(i)=0.0  
        VPrecip1(i, nd+1)=0.0  
315      end do      end do
316    
317      if (iflag_con.eq.3) then      if (iflag_con.eq.3) then
318         do il=1, len         do il = 1, len
319            sig1(il, nd)=sig1(il, nd)+1.            sig1(il, nd) = sig1(il, nd) + 1.
320            sig1(il, nd)=amin1(sig1(il, nd), 12.1)            sig1(il, nd)  =  min(sig1(il, nd), 12.1)
321         enddo         enddo
322      endif      endif
323    
# Line 368  contains Line 326  contains
326      !--------------------------------------------------------------------      !--------------------------------------------------------------------
327    
328      if (iflag_con.eq.3) then      if (iflag_con.eq.3) then
329         CALL cv3_prelim(len, nd, ndp1, t1, q1, p1, ph1, lv1, cpn1, tv1, gz1, &         CALL cv3_prelim(len, nd, nd + 1, t1, q1, p1, ph1, lv1, cpn1, tv1, gz1, &
330              h1, hm1, th1)! nd->na              h1, hm1, th1)
331      endif      endif
332    
333      if (iflag_con.eq.4) then      if (iflag_con.eq.4) then
334         CALL cv_prelim(len, nd, ndp1, t1, q1, p1, ph1 &         CALL cv_prelim(len, nd, nd + 1, t1, q1, p1, ph1 &
335              , lv1, cpn1, tv1, gz1, h1, hm1)              , lv1, cpn1, tv1, gz1, h1, hm1)
336      endif      endif
337    
# Line 413  contains Line 371  contains
371      !-------------------------------------------------------------------      !-------------------------------------------------------------------
372    
373      if (iflag_con.eq.3) then      if (iflag_con.eq.3) then
374         CALL cv3_trigger(len, nd, icb1, plcl1, p1, th1, tv1, tvp1       &         CALL cv3_trigger(len, nd, icb1, plcl1, p1, th1, tv1, tvp1, pbase1, &
375              , pbase1, buoybase1, iflag1, sig1, w01) ! nd->na              buoybase1, iflag1, sig1, w01) ! nd->na
376      endif      endif
377    
378      if (iflag_con.eq.4) then      if (iflag_con.eq.4) then
379         CALL cv_trigger(len, nd, icb1, cbmf1, tv1, tvp1, iflag1)         CALL cv_trigger(len, nd, icb1, cbmf1, tv1, tvp1, iflag1)
380      endif      endif
381    
     !=====================================================================  
382      ! --- IF THIS POINT IS REACHED, MOIST CONVECTIVE ADJUSTMENT IS NECESSARY      ! --- IF THIS POINT IS REACHED, MOIST CONVECTIVE ADJUSTMENT IS NECESSARY
     !=====================================================================  
383    
384      ncum=0      ncum = 0
385      do  i=1, len      do  i = 1, len
386         if(iflag1(i).eq.0)then         if(iflag1(i).eq.0)then
387            ncum=ncum+1            ncum = ncum+1
388            idcum(ncum)=i            idcum(ncum) = i
389         endif         endif
390      end do      end do
391    
# Line 443  contains Line 399  contains
399         !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^         !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
400    
401         if (iflag_con.eq.3) then         if (iflag_con.eq.3) then
402            CALL cv3_compress( len, nloc, ncum, nd, ntra &            CALL cv3_compress(len, nloc, ncum, nd, iflag1, nk1, icb1, icbs1, &
403                 , iflag1, nk1, icb1, icbs1 &                 plcl1, tnk1, qnk1, gznk1, pbase1, buoybase1, t1, q1, qs1, u1, &
404                 , plcl1, tnk1, qnk1, gznk1, pbase1, buoybase1 &                 v1, gz1, th1, h1, lv1, cpn1, p1, ph1, tv1, tp1, tvp1, clw1, &
405                 , t1, q1, qs1, u1, v1, gz1, th1 &                 sig1, w01, iflag, nk, icb, icbs, plcl, tnk, qnk, gznk, pbase, &
406                 , tra1 &                 buoybase, t, q, qs, u, v, gz, th, h, lv, cpn, p, ph, tv, tp, &
407                 , h1, lv1, cpn1, p1, ph1, tv1, tp1, tvp1, clw1  &                 tvp, clw, sig, w0)
                , sig1, w01 &  
                , iflag, nk, icb, icbs &  
                , plcl, tnk, qnk, gznk, pbase, buoybase &  
                , t, q, qs, u, v, gz, th &  
                , tra &  
                , h, lv, cpn, p, ph, tv, tp, tvp, clw  &  
                , sig, w0  )  
408         endif         endif
409    
410         if (iflag_con.eq.4) then         if (iflag_con.eq.4) then
# Line 515  contains Line 464  contains
464         !-------------------------------------------------------------------         !-------------------------------------------------------------------
465    
466         if (iflag_con.eq.3) then         if (iflag_con.eq.3) then
467            CALL cv3_mixing(nloc, ncum, nd, nd, ntra, icb, nk, inb     &            CALL cv3_mixing(nloc, ncum, nd, nd, icb, nk, inb, ph, t, q, &
468                 , ph, t, q, qs, u, v, tra, h, lv, qnk &                 qs, u, v, h, lv, qnk, hp, tv, tvp, ep, clw, m, sig, ment, &
469                 , hp, tv, tvp, ep, clw, m, sig &                 qent, uent, vent, nent, sij, elij, ments, qents)
                , ment, qent, uent, vent, nent, sij, elij, ments, qents, traent)! na->nd  
470         endif         endif
471    
472         if (iflag_con.eq.4) then         if (iflag_con.eq.4) then
# Line 533  contains Line 481  contains
481         !-------------------------------------------------------------------         !-------------------------------------------------------------------
482    
483         if (iflag_con.eq.3) then         if (iflag_con.eq.3) then
484            CALL cv3_unsat(nloc, ncum, nd, nd, ntra, icb, inb     &            CALL cv3_unsat(nloc, ncum, nd, nd, icb, inb     &
485                 , t, q, qs, gz, u, v, tra, p, ph &                 , t, q, qs, gz, u, v, p, ph &
486                 , th, tv, lv, cpn, ep, sigp, clw &                 , th, tv, lv, cpn, ep, sigp, clw &
487                 , m, ment, elij, delt, plcl &                 , m, ment, elij, delt, plcl &
488                 , mp, qp, up, vp, trap, wt, water, evap, b)! na->nd                 , mp, qp, up, vp, wt, water, evap, b)! na->nd
489         endif         endif
490    
491         if (iflag_con.eq.4) then         if (iflag_con.eq.4) then
# Line 553  contains Line 501  contains
501         !-------------------------------------------------------------------         !-------------------------------------------------------------------
502    
503         if (iflag_con.eq.3) then         if (iflag_con.eq.3) then
504            CALL cv3_yield(nloc, ncum, nd, nd, ntra             &            CALL cv3_yield(nloc, ncum, nd, nd             &
505                 , icb, inb, delt &                 , icb, inb, delt &
506                 , t, q, u, v, tra, gz, p, ph, h, hp, lv, cpn, th &                 , t, q, u, v, gz, p, ph, h, hp, lv, cpn, th &
507                 , ep, clw, m, tp, mp, qp, up, vp, trap &                 , ep, clw, m, tp, mp, qp, up, vp &
508                 , wt, water, evap, b &                 , wt, water, evap, b &
509                 , ment, qent, uent, vent, nent, elij, traent, sig &                 , ment, qent, uent, vent, nent, elij, sig &
510                 , tv, tvp &                 , tv, tvp &
511                 , iflag, precip, VPrecip, ft, fq, fu, fv, ftra &                 , iflag, precip, VPrecip, ft, fq, fu, fv &
512                 , upwd, dnwd, dnwd0, ma, mike, tls, tps, qcondc, wd)! na->nd                 , upwd, dnwd, dnwd0, ma, mike, tls, tps, qcondc, wd)! na->nd
513         endif         endif
514    
# Line 587  contains Line 535  contains
535         !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^         !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
536         ! --- UNCOMPRESS THE FIELDS         ! --- UNCOMPRESS THE FIELDS
537         !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^         !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
538         ! set iflag1 =42 for non convective points         ! set iflag1  = 42 for non convective points
539         do  i=1, len         do  i = 1, len
540            iflag1(i)=42            iflag1(i) = 42
541         end do         end do
542         !  
543         if (iflag_con.eq.3) then         if (iflag_con.eq.3) then
544            CALL cv3_uncompress(nloc, len, ncum, nd, ntra, idcum &            CALL cv3_uncompress(nloc, len, ncum, nd, idcum &
545                 , iflag &                 , iflag &
546                 , precip, VPrecip, sig, w0 &                 , precip, VPrecip, sig, w0 &
547                 , ft, fq, fu, fv, ftra &                 , ft, fq, fu, fv &
548                 , inb  &                 , inb  &
549                 , Ma, upwd, dnwd, dnwd0, qcondc, wd, cape &                 , Ma, upwd, dnwd, dnwd0, qcondc, wd, cape &
550                 , da, phi, mp &                 , da, phi, mp &
551                 , iflag1 &                 , iflag1 &
552                 , precip1, VPrecip1, sig1, w01 &                 , precip1, VPrecip1, sig1, w01 &
553                 , ft1, fq1, fu1, fv1, ftra1 &                 , ft1, fq1, fu1, fv1 &
554                 , inb1 &                 , inb1 &
555                 , Ma1, upwd1, dnwd1, dnwd01, qcondc1, wd1, cape1  &                 , Ma1, upwd1, dnwd1, dnwd01, qcondc1, wd1, cape1  &
556                 , da1, phi1, mp1)                 , da1, phi1, mp1)

Legend:
Removed from v.52  
changed lines
  Added in v.97

  ViewVC Help
Powered by ViewVC 1.1.21