/[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 62 by guez, Thu Jul 26 14:37:37 2012 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        ! Main driver for convection
15    
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      USE dimphy, ONLY: klev, klon
33    
34      ! PARAMETERS:      ! PARAMETERS:
# Line 21  contains Line 39  contains
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 39  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
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
64    
     ! 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)  
   
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 74  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, intent(out):: upwd1(len, nd) ! total upward mass flux (adiab+mixed)      real, intent(out):: upwd1(len, nd) ! total upward mass flux (adiab+mixed)
96      real, intent(out):: dnwd1(len, nd) ! saturated downward mass flux (mixed)      real, intent(out):: dnwd1(len, nd) ! saturated downward mass flux (mixed)
# Line 87  contains Line 101  contains
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
# Line 205  contains Line 214  contains
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 230  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
# Line 290  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    
# Line 349  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 404  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 434  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

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

  ViewVC Help
Powered by ViewVC 1.1.21