/[lmdze]/trunk/libf/phylmd/cv_driver.f90
ViewVC logotype

Diff of /trunk/libf/phylmd/cv_driver.f90

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

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

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

  ViewVC Help
Powered by ViewVC 1.1.21