/[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 69 by guez, Mon Feb 18 16:33:12 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      !      use clesphys2, only: iflag_con
17        use cv3_param_m, only: cv3_param
18        USE dimphy, ONLY: klev, klon
19    
20      ! PARAMETERS:      ! PARAMETERS:
21      !      Name            Type         Usage            Description      !      Name            Type         Usage            Description
22      !   ----------      ----------     -------  ----------------------------      !   ----------      ----------     -------  ----------------------------
23      !  
24      !      len           Integer        Input        first (i) dimension      !      len           Integer        Input        first (i) dimension
25      !      nd            Integer        Input        vertical (k) dimension      !      nd            Integer        Input        vertical (k) dimension
26      !      ndp1          Integer        Input        nd + 1      !      ndp1          Integer        Input        nd + 1
27      !      ntra          Integer        Input        number of tracors      !      ntra          Integer        Input        number of tracors
     !      iflag_con     Integer        Input        version of convect (3/4)  
28      !      t1            Real           Input        temperature      !      t1            Real           Input        temperature
29      !      q1            Real           Input        specific hum      !      q1            Real           Input        specific hum
30      !      qs1           Real           Input        sat specific hum      !      qs1           Real           Input        sat specific hum
# Line 44  contains Line 46  contains
46      !      w01           Real           In/Out       vertical velocity within adiab updraft      !      w01           Real           In/Out       vertical velocity within adiab updraft
47      !      delt          Real           Input        time step      !      delt          Real           Input        time step
48      !      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  
49      !      qcondc1       Real           Output       in-cld mixing ratio of condensed water      !      qcondc1       Real           Output       in-cld mixing ratio of condensed water
50      !      wd1           Real           Output       downdraft velocity scale for sfc fluxes      !      wd1           Real           Output       downdraft velocity scale for sfc fluxes
51      !      cape1         Real           Output       CAPE      !      cape1         Real           Output       CAPE
52      !  
53      ! S. Bony, Mar 2002:      ! S. Bony, Mar 2002:
54      !     * Several modules corresponding to different physical processes      !     * Several modules corresponding to different physical processes
55      !     * Several versions of convect may be used:      !     * Several versions of convect may be used:
# Line 59  contains Line 58  contains
58      !   + tard:    - iflag_con=5: version lmd with ice (previously named convectg)      !   + tard:    - iflag_con=5: version lmd with ice (previously named convectg)
59      ! S. Bony, Oct 2002:      ! S. Bony, Oct 2002:
60      !     * Vectorization of convect3 (ie version lmd)      !     * Vectorization of convect3 (ie version lmd)
     !  
     !..............................END PROLOGUE.............................  
     !  
     !  
61    
62      integer len      integer len
63      integer nd      integer nd
64      integer ndp1      integer ndp1
65      integer noff      integer noff
66      integer, intent(in):: iflag_con      integer, intent(in):: ntra
     integer ntra  
67      real, intent(in):: t1(len, nd)      real, intent(in):: t1(len, nd)
68      real q1(len, nd)      real q1(len, nd)
69      real qs1(len, nd)      real qs1(len, nd)
# Line 86  contains Line 80  contains
80      real cbmf1(len)      real cbmf1(len)
81      real VPrecip1(len, nd+1)      real VPrecip1(len, nd+1)
82      real Ma1(len, nd)      real Ma1(len, nd)
83      real upwd1(len, nd)      real, intent(out):: upwd1(len, nd) ! total upward mass flux (adiab+mixed)
84      real dnwd1(len, nd)      real, intent(out):: dnwd1(len, nd) ! saturated downward mass flux (mixed)
85      real dnwd01(len, nd)      real, intent(out):: dnwd01(len, nd) ! unsaturated downward mass flux
86    
87      real qcondc1(len, nd)     ! cld      real qcondc1(len, nd)     ! cld
88      real wd1(len)            ! gust      real wd1(len)            ! gust
# Line 105  contains Line 99  contains
99      ! --- ARGUMENTS      ! --- ARGUMENTS
100      !-------------------------------------------------------------------      !-------------------------------------------------------------------
101      ! --- On input:      ! --- On input:
102      !  
103      !  t:   Array of absolute temperature (K) of dimension ND, with first      !  t:   Array of absolute temperature (K) of dimension ND, with first
104      !       index corresponding to lowest model level. Note that this array      !       index corresponding to lowest model level. Note that this array
105      !       will be altered by the subroutine if dry convective adjustment      !       will be altered by the subroutine if dry convective adjustment
106      !       occurs and if IPBL is not equal to 0.      !       occurs and if IPBL is not equal to 0.
107      !  
108      !  q:   Array of specific humidity (gm/gm) of dimension ND, with first      !  q:   Array of specific humidity (gm/gm) of dimension ND, with first
109      !       index corresponding to lowest model level. Must be defined      !       index corresponding to lowest model level. Must be defined
110      !       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
111      !       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.
112      !  
113      !  qs:  Array of saturation specific humidity of dimension ND, with first      !  qs:  Array of saturation specific humidity of dimension ND, with first
114      !       index corresponding to lowest model level. Must be defined      !       index corresponding to lowest model level. Must be defined
115      !       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
116      !       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.
117      !  
118      !  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
119      !       index corresponding with the lowest model level. Defined at      !       index corresponding with the lowest model level. Defined at
120      !       same levels as T. Note that this array will be altered if      !       same levels as T. Note that this array will be altered if
121      !       dry convective adjustment occurs and if IPBL is not equal to 0.      !       dry convective adjustment occurs and if IPBL is not equal to 0.
122      !  
123      !  v:   Same as u but for meridional velocity.      !  v:   Same as u but for meridional velocity.
124      !  
125      !  tra: Array of passive tracer mixing ratio, of dimensions (ND, NTRA),      !  tra: Array of passive tracer mixing ratio, of dimensions (ND, NTRA),
126      !       where NTRA is the number of different tracers. If no      !       where NTRA is the number of different tracers. If no
127      !       convective tracer transport is needed, define a dummy      !       convective tracer transport is needed, define a dummy
128      !       input array of dimension (ND, 1). Tracers are defined at      !       input array of dimension (ND, 1). Tracers are defined at
129      !       same vertical levels as T. Note that this array will be altered      !       same vertical levels as T. Note that this array will be altered
130      !       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.
131      !  
132      !  p:   Array of pressure (mb) of dimension ND, with first      !  p:   Array of pressure (mb) of dimension ND, with first
133      !       index corresponding to lowest model level. Must be defined      !       index corresponding to lowest model level. Must be defined
134      !       at same grid levels as T.      !       at same grid levels as T.
135      !  
136      !  ph:  Array of pressure (mb) of dimension ND+1, with first index      !  ph:  Array of pressure (mb) of dimension ND+1, with first index
137      !       corresponding to lowest level. These pressures are defined at      !       corresponding to lowest level. These pressures are defined at
138      !       levels intermediate between those of P, T, Q and QS. The first      !       levels intermediate between those of P, T, Q and QS. The first
139      !       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)
140      !       the first value of the array P.      !       the first value of the array P.
141      !  
142      !  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.
143      !       NL MUST be less than or equal to ND-1.      !       NL MUST be less than or equal to ND-1.
144      !  
145      !  delt: The model time step (sec) between calls to CONVECT      !  delt: The model time step (sec) between calls to CONVECT
146      !  
147      !----------------------------------------------------------------------------      !----------------------------------------------------------------------------
148      ! ---   On Output:      ! ---   On Output:
149      !  
150      !  iflag: An output integer whose value denotes the following:      !  iflag: An output integer whose value denotes the following:
151      !       VALUE   INTERPRETATION      !       VALUE   INTERPRETATION
152      !       -----   --------------      !       -----   --------------
# Line 171  contains Line 165  contains
165      !               level is above the 200 mb level.      !               level is above the 200 mb level.
166      !         9     No moist convection: cloud base is higher      !         9     No moist convection: cloud base is higher
167      !               then the level NL-1.      !               then the level NL-1.
168      !  
169      !  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
170      !        grid levels as T, Q, QS and P.      !        grid levels as T, Q, QS and P.
171      !  
172      !  fq:   Array of specific humidity tendencies ((gm/gm)/s) of dimension ND,      !  fq:   Array of specific humidity tendencies ((gm/gm)/s) of dimension ND,
173      !        defined at same grid levels as T, Q, QS and P.      !        defined at same grid levels as T, Q, QS and P.
174      !  
175      !  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,
176      !        defined at same grid levels as T.      !        defined at same grid levels as T.
177      !  
178      !  fv:   Same as FU, but for forcing of meridional velocity.      !  fv:   Same as FU, but for forcing of meridional velocity.
179      !  
180      !  ftra: Array of forcing of tracer content, in tracer mixing ratio per      !  ftra: Array of forcing of tracer content, in tracer mixing ratio per
181      !        second, defined at same levels as T. Dimensioned (ND, NTRA).      !        second, defined at same levels as T. Dimensioned (ND, NTRA).
182      !  
183      !  precip: Scalar convective precipitation rate (mm/day).      !  precip: Scalar convective precipitation rate (mm/day).
184      !  
185      !  VPrecip: Vertical profile of convective precipitation (kg/m2/s).      !  VPrecip: Vertical profile of convective precipitation (kg/m2/s).
186      !  
187      !  wd:   A convective downdraft velocity scale. For use in surface      !  wd:   A convective downdraft velocity scale. For use in surface
188      !        flux parameterizations. See convect.ps file for details.      !        flux parameterizations. See convect.ps file for details.
189      !  
190      !  tprime: A convective downdraft temperature perturbation scale (K).      !  tprime: A convective downdraft temperature perturbation scale (K).
191      !          For use in surface flux parameterizations. See convect.ps      !          For use in surface flux parameterizations. See convect.ps
192      !          file for details.      !          file for details.
193      !  
194      !  qprime: A convective downdraft specific humidity      !  qprime: A convective downdraft specific humidity
195      !          perturbation scale (gm/gm).      !          perturbation scale (gm/gm).
196      !          For use in surface flux parameterizations. See convect.ps      !          For use in surface flux parameterizations. See convect.ps
197      !          file for details.      !          file for details.
198      !  
199      !  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
200      !        BE STORED BY THE CALLING PROGRAM AND RETURNED TO CONVECT AT      !        BE STORED BY THE CALLING PROGRAM AND RETURNED TO CONVECT AT
201      !        ITS NEXT CALL. That is, the value of CBMF must be "remembered"      !        ITS NEXT CALL. That is, the value of CBMF must be "remembered"
202      !        by the calling program between calls to CONVECT.      !        by the calling program between calls to CONVECT.
203      !  
204      !  det:   Array of detrainment mass flux of dimension ND.      !  det:   Array of detrainment mass flux of dimension ND.
205      !  
206      !-------------------------------------------------------------------      !-------------------------------------------------------------------
207      !  
208      !  Local arrays      !  Local arrays
     !  
209    
210      integer i, k, n, il, j      integer i, k, n, il, j
211      integer icbmax      integer icbmax
# Line 242  contains Line 235  contains
235      real sig1(klon, klev)      real sig1(klon, klev)
236      real w01(klon, klev)      real w01(klon, klev)
237      real th1(klon, klev)      real th1(klon, klev)
238      !  
239      integer ncum      integer ncum
240      !  
241      ! (local) compressed fields:      ! (local) compressed fields:
242      !  
243      integer nloc      integer nloc
244      parameter (nloc=klon) ! pour l'instant      parameter (nloc=klon) ! pour l'instant
245    
# Line 299  contains Line 292  contains
292      ! -- set thermodynamical constants:      ! -- set thermodynamical constants:
293      !     (common cvthermo)      !     (common cvthermo)
294    
295      CALL cv_thermo(iflag_con)      CALL cv_thermo
296    
297      ! -- set convect parameters      ! -- set convect parameters
298      !  
299      !     includes microphysical parameters and parameters that      !     includes microphysical parameters and parameters that
300      !     control the rate of approach to quasi-equilibrium)      !     control the rate of approach to quasi-equilibrium)
301      !     (common cvparam)      !     (common cvparam)
# Line 591  contains Line 584  contains
584         do  i=1, len         do  i=1, len
585            iflag1(i)=42            iflag1(i)=42
586         end do         end do
587         !  
588         if (iflag_con.eq.3) then         if (iflag_con.eq.3) then
589            CALL cv3_uncompress(nloc, len, ncum, nd, ntra, idcum &            CALL cv3_uncompress(nloc, len, ncum, nd, ntra, idcum &
590                 , iflag &                 , iflag &

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

  ViewVC Help
Powered by ViewVC 1.1.21