/[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 52 by guez, Fri Sep 23 12:28:01 2011 UTC revision 72 by guez, Tue Jul 23 13:00:07 2013 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, ndp1, ntra, t1, q1, qs1, u1, v1, tra1, p1, &
8         tra1, p1, ph1, iflag1, ft1, fq1, fu1, fv1, ftra1, precip1, VPrecip1, &         ph1, iflag1, ft1, fq1, fu1, fv1, ftra1, precip1, VPrecip1, cbmf1, &
9         cbmf1, sig1, w01, icb1, inb1, delt, Ma1, upwd1, dnwd1, dnwd01, &         sig1, w01, icb1, inb1, delt, Ma1, upwd1, dnwd1, dnwd01, qcondc1, wd1, &
10         qcondc1, wd1, cape1, da1, phi1, mp1)         cape1, da1, phi1, mp1)
11    
12      ! From LMDZ4/libf/phylmd/cv_driver.F, version 1.3 2005/04/15 12:36:17      ! From LMDZ4/libf/phylmd/cv_driver.F, version 1.3 2005/04/15 12:36:17
13    
14      use dimens_m      ! Main driver for convection
15      use dimphy  
16      !      ! S. Bony, Mar 2002:
17    
18        ! Several modules corresponding to different physical processes
19    
20        ! Several versions of convect may be used:
21        ! - iflag_con=3: version lmd  (previously named convect3)
22        ! - iflag_con=4: version 4.3b (vect. version, previously convect1/2)
23    
24        ! Plus tard :
25        ! - iflag_con=5: version lmd with ice (previously named convectg)
26    
27        ! S. Bony, Oct 2002:
28        ! Vectorization of convect3 (ie version lmd)
29    
30        use clesphys2, only: iflag_con
31        use cv3_param_m, only: cv3_param
32        USE dimphy, ONLY: klev, klon
33    
34      ! PARAMETERS:      ! PARAMETERS:
35      !      Name            Type         Usage            Description      !      Name            Type         Usage            Description
36      !   ----------      ----------     -------  ----------------------------      !   ----------      ----------     -------  ----------------------------
37      !  
38      !      len           Integer        Input        first (i) dimension      !      len           Integer        Input        first (i) dimension
39      !      nd            Integer        Input        vertical (k) dimension      !      nd            Integer        Input        vertical (k) dimension
40      !      ndp1          Integer        Input        nd + 1      !      ndp1          Integer        Input        nd + 1
41      !      ntra          Integer        Input        number of tracors      !      ntra          Integer        Input        number of tracors
     !      iflag_con     Integer        Input        version of convect (3/4)  
42      !      t1            Real           Input        temperature      !      t1            Real           Input        temperature
43      !      q1            Real           Input        specific hum      !      q1            Real           Input        specific hum
44      !      qs1           Real           Input        sat specific hum      !      qs1           Real           Input        sat specific hum
# Line 40  contains Line 56  contains
56      !      precip1       Real           Output       precipitation      !      precip1       Real           Output       precipitation
57      !      VPrecip1      Real           Output       vertical profile of precipitations      !      VPrecip1      Real           Output       vertical profile of precipitations
58      !      cbmf1         Real           Output       cloud base mass flux      !      cbmf1         Real           Output       cloud base mass flux
     !      sig1          Real           In/Out       section adiabatic updraft  
     !      w01           Real           In/Out       vertical velocity within adiab updraft  
59      !      delt          Real           Input        time step      !      delt          Real           Input        time step
60      !      Ma1           Real           Output       mass flux adiabatic updraft      !      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  
61      !      qcondc1       Real           Output       in-cld mixing ratio of condensed water      !      qcondc1       Real           Output       in-cld mixing ratio of condensed water
62      !      wd1           Real           Output       downdraft velocity scale for sfc fluxes      !      wd1           Real           Output       downdraft velocity scale for sfc fluxes
63      !      cape1         Real           Output       CAPE      !      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.............................  
     !  
     !  
64    
65      integer len      integer len
66      integer nd      integer nd
67      integer ndp1      integer ndp1
68      integer noff      integer, intent(in):: ntra
     integer, intent(in):: iflag_con  
     integer ntra  
69      real, intent(in):: t1(len, nd)      real, intent(in):: t1(len, nd)
70      real q1(len, nd)      real q1(len, nd)
71      real qs1(len, nd)      real qs1(len, nd)
72      real u1(len, nd)      real u1(len, nd)
73      real v1(len, nd)      real v1(len, nd)
74        real, intent(in):: tra1(len, nd, ntra)
75      real p1(len, nd)      real p1(len, nd)
76      real ph1(len, ndp1)      real ph1(len, ndp1)
77      integer iflag1(len)      integer iflag1(len)
# Line 82  contains Line 79  contains
79      real fq1(len, nd)      real fq1(len, nd)
80      real fu1(len, nd)      real fu1(len, nd)
81      real fv1(len, nd)      real fv1(len, nd)
82        real ftra1(len, nd, ntra)
83      real precip1(len)      real precip1(len)
     real cbmf1(len)  
84      real VPrecip1(len, nd+1)      real VPrecip1(len, nd+1)
85        real cbmf1(len)
86        real, intent(inout):: sig1(klon, klev) ! section adiabatic updraft
87    
88        real, intent(inout):: w01(klon, klev)
89        ! vertical velocity within adiabatic updraft
90    
91        integer icb1(klon)
92        integer inb1(klon)
93        real, intent(in):: delt
94      real Ma1(len, nd)      real Ma1(len, nd)
95      real upwd1(len, nd)      real, intent(out):: upwd1(len, nd) ! total upward mass flux (adiab+mixed)
96      real dnwd1(len, nd)      real, intent(out):: dnwd1(len, nd) ! saturated downward mass flux (mixed)
97      real dnwd01(len, nd)      real, intent(out):: dnwd01(len, nd) ! unsaturated downward mass flux
98    
99      real qcondc1(len, nd)     ! cld      real qcondc1(len, nd)     ! cld
100      real wd1(len)            ! gust      real wd1(len)            ! gust
101      real cape1(len)      real cape1(len)
102    
103      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  
104    
105      !-------------------------------------------------------------------      !-------------------------------------------------------------------
106      ! --- ARGUMENTS      ! --- ARGUMENTS
107      !-------------------------------------------------------------------      !-------------------------------------------------------------------
108      ! --- On input:      ! --- On input:
109      !  
110      !  t:   Array of absolute temperature (K) of dimension ND, with first      !  t:   Array of absolute temperature (K) of dimension ND, with first
111      !       index corresponding to lowest model level. Note that this array      !       index corresponding to lowest model level. Note that this array
112      !       will be altered by the subroutine if dry convective adjustment      !       will be altered by the subroutine if dry convective adjustment
113      !       occurs and if IPBL is not equal to 0.      !       occurs and if IPBL is not equal to 0.
114      !  
115      !  q:   Array of specific humidity (gm/gm) of dimension ND, with first      !  q:   Array of specific humidity (gm/gm) of dimension ND, with first
116      !       index corresponding to lowest model level. Must be defined      !       index corresponding to lowest model level. Must be defined
117      !       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
118      !       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.
119      !  
120      !  qs:  Array of saturation specific humidity of dimension ND, with first      !  qs:  Array of saturation specific humidity of dimension ND, with first
121      !       index corresponding to lowest model level. Must be defined      !       index corresponding to lowest model level. Must be defined
122      !       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
123      !       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.
124      !  
125      !  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
126      !       index corresponding with the lowest model level. Defined at      !       index corresponding with the lowest model level. Defined at
127      !       same levels as T. Note that this array will be altered if      !       same levels as T. Note that this array will be altered if
128      !       dry convective adjustment occurs and if IPBL is not equal to 0.      !       dry convective adjustment occurs and if IPBL is not equal to 0.
129      !  
130      !  v:   Same as u but for meridional velocity.      !  v:   Same as u but for meridional velocity.
131      !  
132      !  tra: Array of passive tracer mixing ratio, of dimensions (ND, NTRA),      !  tra: Array of passive tracer mixing ratio, of dimensions (ND, NTRA),
133      !       where NTRA is the number of different tracers. If no      !       where NTRA is the number of different tracers. If no
134      !       convective tracer transport is needed, define a dummy      !       convective tracer transport is needed, define a dummy
135      !       input array of dimension (ND, 1). Tracers are defined at      !       input array of dimension (ND, 1). Tracers are defined at
136      !       same vertical levels as T. Note that this array will be altered      !       same vertical levels as T. Note that this array will be altered
137      !       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.
138      !  
139      !  p:   Array of pressure (mb) of dimension ND, with first      !  p:   Array of pressure (mb) of dimension ND, with first
140      !       index corresponding to lowest model level. Must be defined      !       index corresponding to lowest model level. Must be defined
141      !       at same grid levels as T.      !       at same grid levels as T.
142      !  
143      !  ph:  Array of pressure (mb) of dimension ND+1, with first index      !  ph:  Array of pressure (mb) of dimension ND+1, with first index
144      !       corresponding to lowest level. These pressures are defined at      !       corresponding to lowest level. These pressures are defined at
145      !       levels intermediate between those of P, T, Q and QS. The first      !       levels intermediate between those of P, T, Q and QS. The first
146      !       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)
147      !       the first value of the array P.      !       the first value of the array P.
148      !  
149      !  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.
150      !       NL MUST be less than or equal to ND-1.      !       NL MUST be less than or equal to ND-1.
151      !  
152      !  delt: The model time step (sec) between calls to CONVECT      !  delt: The model time step (sec) between calls to CONVECT
153      !  
154      !----------------------------------------------------------------------------      !----------------------------------------------------------------------------
155      ! ---   On Output:      ! ---   On Output:
156      !  
157      !  iflag: An output integer whose value denotes the following:      !  iflag: An output integer whose value denotes the following:
158      !       VALUE   INTERPRETATION      !       VALUE   INTERPRETATION
159      !       -----   --------------      !       -----   --------------
# Line 171  contains Line 172  contains
172      !               level is above the 200 mb level.      !               level is above the 200 mb level.
173      !         9     No moist convection: cloud base is higher      !         9     No moist convection: cloud base is higher
174      !               then the level NL-1.      !               then the level NL-1.
175      !  
176      !  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
177      !        grid levels as T, Q, QS and P.      !        grid levels as T, Q, QS and P.
178      !  
179      !  fq:   Array of specific humidity tendencies ((gm/gm)/s) of dimension ND,      !  fq:   Array of specific humidity tendencies ((gm/gm)/s) of dimension ND,
180      !        defined at same grid levels as T, Q, QS and P.      !        defined at same grid levels as T, Q, QS and P.
181      !  
182      !  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,
183      !        defined at same grid levels as T.      !        defined at same grid levels as T.
184      !  
185      !  fv:   Same as FU, but for forcing of meridional velocity.      !  fv:   Same as FU, but for forcing of meridional velocity.
186      !  
187      !  ftra: Array of forcing of tracer content, in tracer mixing ratio per      !  ftra: Array of forcing of tracer content, in tracer mixing ratio per
188      !        second, defined at same levels as T. Dimensioned (ND, NTRA).      !        second, defined at same levels as T. Dimensioned (ND, NTRA).
189      !  
190      !  precip: Scalar convective precipitation rate (mm/day).      !  precip: Scalar convective precipitation rate (mm/day).
191      !  
192      !  VPrecip: Vertical profile of convective precipitation (kg/m2/s).      !  VPrecip: Vertical profile of convective precipitation (kg/m2/s).
193      !  
194      !  wd:   A convective downdraft velocity scale. For use in surface      !  wd:   A convective downdraft velocity scale. For use in surface
195      !        flux parameterizations. See convect.ps file for details.      !        flux parameterizations. See convect.ps file for details.
196      !  
197      !  tprime: A convective downdraft temperature perturbation scale (K).      !  tprime: A convective downdraft temperature perturbation scale (K).
198      !          For use in surface flux parameterizations. See convect.ps      !          For use in surface flux parameterizations. See convect.ps
199      !          file for details.      !          file for details.
200      !  
201      !  qprime: A convective downdraft specific humidity      !  qprime: A convective downdraft specific humidity
202      !          perturbation scale (gm/gm).      !          perturbation scale (gm/gm).
203      !          For use in surface flux parameterizations. See convect.ps      !          For use in surface flux parameterizations. See convect.ps
204      !          file for details.      !          file for details.
205      !  
206      !  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
207      !        BE STORED BY THE CALLING PROGRAM AND RETURNED TO CONVECT AT      !        BE STORED BY THE CALLING PROGRAM AND RETURNED TO CONVECT AT
208      !        ITS NEXT CALL. That is, the value of CBMF must be "remembered"      !        ITS NEXT CALL. That is, the value of CBMF must be "remembered"
209      !        by the calling program between calls to CONVECT.      !        by the calling program between calls to CONVECT.
210      !  
211      !  det:   Array of detrainment mass flux of dimension ND.      !  det:   Array of detrainment mass flux of dimension ND.
212      !  
213      !-------------------------------------------------------------------      !-------------------------------------------------------------------
214      !  
215      !  Local arrays      !  Local arrays
216      !  
217        integer noff
218        real da(len, nd), phi(len, nd, nd), mp(len, nd)
219    
220      integer i, k, n, il, j      integer i, k, n, il, j
221      integer icbmax      integer icbmax
222      integer nk1(klon)      integer nk1(klon)
     integer icb1(klon)  
     integer inb1(klon)  
223      integer icbs1(klon)      integer icbs1(klon)
224    
225      real plcl1(klon)      real plcl1(klon)
# Line 239  contains Line 240  contains
240      real tp1(klon, klev)      real tp1(klon, klev)
241      real tvp1(klon, klev)      real tvp1(klon, klev)
242      real clw1(klon, klev)      real clw1(klon, klev)
     real sig1(klon, klev)  
     real w01(klon, klev)  
243      real th1(klon, klev)      real th1(klon, klev)
244      !  
245      integer ncum      integer ncum
246      !  
247      ! (local) compressed fields:      ! (local) compressed fields:
248      !  
249      integer nloc      integer nloc
250      parameter (nloc=klon) ! pour l'instant      parameter (nloc=klon) ! pour l'instant
251    
# Line 299  contains Line 298  contains
298      ! -- set thermodynamical constants:      ! -- set thermodynamical constants:
299      !     (common cvthermo)      !     (common cvthermo)
300    
301      CALL cv_thermo(iflag_con)      CALL cv_thermo
302    
303      ! -- set convect parameters      ! -- set convect parameters
304      !  
305      !     includes microphysical parameters and parameters that      !     includes microphysical parameters and parameters that
306      !     control the rate of approach to quasi-equilibrium)      !     control the rate of approach to quasi-equilibrium)
307      !     (common cvparam)      !     (common cvparam)
# Line 358  contains Line 357  contains
357    
358      if (iflag_con.eq.3) then      if (iflag_con.eq.3) then
359         do il=1, len         do il=1, len
360            sig1(il, nd)=sig1(il, nd)+1.            sig1(il, nd)=sig1(il, nd) + 1.
361            sig1(il, nd)=amin1(sig1(il, nd), 12.1)            sig1(il, nd) = min(sig1(il, nd), 12.1)
362         enddo         enddo
363      endif      endif
364    
# Line 413  contains Line 412  contains
412      !-------------------------------------------------------------------      !-------------------------------------------------------------------
413    
414      if (iflag_con.eq.3) then      if (iflag_con.eq.3) then
415         CALL cv3_trigger(len, nd, icb1, plcl1, p1, th1, tv1, tvp1       &         CALL cv3_trigger(len, nd, icb1, plcl1, p1, th1, tv1, tvp1, pbase1, &
416              , pbase1, buoybase1, iflag1, sig1, w01) ! nd->na              buoybase1, iflag1, sig1, w01) ! nd->na
417      endif      endif
418    
419      if (iflag_con.eq.4) then      if (iflag_con.eq.4) then
# Line 443  contains Line 442  contains
442         !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^         !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
443    
444         if (iflag_con.eq.3) then         if (iflag_con.eq.3) then
445            CALL cv3_compress( len, nloc, ncum, nd, ntra &            CALL cv3_compress(len, nloc, ncum, nd, ntra, iflag1, nk1, icb1, &
446                 , iflag1, nk1, icb1, icbs1 &                 icbs1, plcl1, tnk1, qnk1, gznk1, pbase1, buoybase1, t1, q1, &
447                 , plcl1, tnk1, qnk1, gznk1, pbase1, buoybase1 &                 qs1, u1, v1, gz1, th1, tra1, h1, lv1, cpn1, p1, ph1, tv1, tp1, &
448                 , t1, q1, qs1, u1, v1, gz1, th1 &                 tvp1, clw1, sig1, w01, iflag, nk, icb, icbs, plcl, tnk, qnk, &
449                 , tra1 &                 gznk, pbase, buoybase, t, q, qs, u, v, gz, th, tra, h, lv, &
450                 , h1, lv1, cpn1, p1, ph1, tv1, tp1, tvp1, clw1  &                 cpn, p, ph, tv, tp, 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  )  
451         endif         endif
452    
453         if (iflag_con.eq.4) then         if (iflag_con.eq.4) then
# Line 591  contains Line 583  contains
583         do  i=1, len         do  i=1, len
584            iflag1(i)=42            iflag1(i)=42
585         end do         end do
586         !  
587         if (iflag_con.eq.3) then         if (iflag_con.eq.3) then
588            CALL cv3_uncompress(nloc, len, ncum, nd, ntra, idcum &            CALL cv3_uncompress(nloc, len, ncum, nd, ntra, idcum &
589                 , iflag &                 , iflag &

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

  ViewVC Help
Powered by ViewVC 1.1.21