/[lmdze]/trunk/phylmd/cv_driver.f
ViewVC logotype

Diff of /trunk/phylmd/cv_driver.f

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

revision 96 by guez, Wed Mar 26 17:18:58 2014 UTC 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, t1, q1, qs1, u1, v1, tra1, p1, &    SUBROUTINE cv_driver(len, nd, t1, q1, qs1, u1, v1, p1, ph1, iflag1, ft1, &
8         ph1, iflag1, ft1, fq1, fu1, fv1, ftra1, precip1, VPrecip1, cbmf1, &         fq1, fu1, fv1, precip1, VPrecip1, cbmf1, sig1, w01, icb1, inb1, delt, &
9         sig1, w01, icb1, inb1, delt, Ma1, upwd1, dnwd1, dnwd01, qcondc1, wd1, &         Ma1, upwd1, dnwd1, dnwd01, qcondc1, wd1, cape1, da1, phi1, mp1)
        cape1, da1, phi1, mp1)  
10    
11      ! 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
   
12      ! Main driver for convection      ! Main driver for convection
13        ! Author: S. Bony, March 2002
     ! S. Bony, March 2002:  
14    
15      ! Several modules corresponding to different physical processes      ! Several modules corresponding to different physical processes
16    
17      ! Several versions of convect may be used:      ! Several versions of convect may be used:
18      ! - iflag_con = 3: version lmd  (previously named convect3)      ! - iflag_con = 3: version lmd
19      ! - iflag_con = 4: version 4.3b (vect. version, previously convect1/2)      ! - iflag_con = 4: version 4.3b
   
     ! Plus tard :  
     ! - iflag_con = 5: version lmd with ice (previously named convectg)  
   
     ! S. Bony, Oct 2002:  
     ! Vectorization of convect3 (ie version lmd)  
20    
21      use clesphys2, only: iflag_con      use clesphys2, only: iflag_con
22      use cv3_compress_m, only: cv3_compress      use cv3_compress_m, only: cv3_compress
23        use cv3_mixing_m, only: cv3_mixing
24      use cv3_param_m, only: cv3_param      use cv3_param_m, only: cv3_param
25        use cv3_prelim_m, only: cv3_prelim
26        use cv3_tracer_m, only: cv3_tracer
27        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      USE dimphy, ONLY: klev, klon
32    
33      ! PARAMETERS:      integer, intent(in):: len ! first dimension
34      !      Name            Type         Usage            Description      integer, intent(in):: nd ! vertical dimension
35      !   ----------      ----------     -------  ----------------------------      real, intent(in):: t1(len, nd) ! temperature
36        real q1(len, nd) !           Input        specific hum
37      !      len           Integer        Input        first (i) dimension      real qs1(len, nd)
     !      nd            Integer        Input        vertical (k) dimension  
     !      ndp1          Integer        Input        nd + 1  
     !      ntra          Integer        Input        number of tracors  
     !      t1            Real           Input        temperature  
     !      q1            Real           Input        specific hum  
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
     !      iflag1        Integer        Output       flag for Emanuel conditions  
     !      ft1           Real           Output       temp tend  
     !      fq1           Real           Output       spec hum tend  
     !      fu1           Real           Output       u-wind tend  
     !      fv1           Real           Output       v-wind tend  
     !      ftra1         Real           Output       tracor tend  
     !      precip1       Real           Output       precipitation  
     !      VPrecip1      Real           Output       vertical profile of precipitations  
     !      cbmf1         Real           Output       cloud base mass flux  
     !      delt          Real           Input        time step  
     !      Ma1           Real           Output       mass flux adiabatic updraft  
     !      qcondc1       Real           Output       in-cld mixing ratio of condensed water  
     !      wd1           Real           Output       downdraft velocity scale for sfc fluxes  
     !      cape1         Real           Output       CAPE  
   
     integer len  
     integer nd  
     integer ndp1  
     integer, intent(in):: ntra  
     real, intent(in):: t1(len, nd)  
     real q1(len, nd)  
     real qs1(len, nd)  
     real, intent(in):: u1(len, nd)  
     real, intent(in):: v1(len, nd)  
     real, intent(in):: tra1(len, nd, ntra)  
     real p1(len, nd)  
     real ph1(len, ndp1)  
47      integer iflag1(len)      integer iflag1(len)
48        !      iflag1        Integer        Output       flag for Emanuel conditions
49      real ft1(len, nd)      real ft1(len, nd)
50        !      ft1           Real           Output       temp tend
51      real fq1(len, nd)      real fq1(len, nd)
52        !      fq1           Real           Output       spec hum tend
53      real fu1(len, nd)      real fu1(len, nd)
54        !      fu1           Real           Output       u-wind tend
55      real fv1(len, nd)      real fv1(len, nd)
56      real ftra1(len, nd, ntra)      !      fv1           Real           Output       v-wind tend
57      real precip1(len)      real precip1(len)
58        !      precip1       Real           Output       precipitation
59      real VPrecip1(len, nd+1)      real VPrecip1(len, nd+1)
60        !      VPrecip1      Real           Output       vertical profile of precipitations
61      real cbmf1(len)      real cbmf1(len)
62        !      cbmf1         Real           Output       cloud base mass flux
63      real, intent(inout):: sig1(klon, klev) ! section adiabatic updraft      real, intent(inout):: sig1(klon, klev) ! section adiabatic updraft
64    
65      real, intent(inout):: w01(klon, klev)      real, intent(inout):: w01(klon, klev)
# Line 92  contains Line 68  contains
68      integer icb1(klon)      integer icb1(klon)
69      integer inb1(klon)      integer inb1(klon)
70      real, intent(in):: delt      real, intent(in):: delt
71        !      delt          Real           Input        time step
72      real Ma1(len, nd)      real Ma1(len, nd)
73        !      Ma1           Real           Output       mass flux adiabatic updraft
74      real, intent(out):: upwd1(len, nd) ! total upward mass flux (adiab+mixed)      real, intent(out):: upwd1(len, nd) ! total upward mass flux (adiab+mixed)
75      real, intent(out):: dnwd1(len, nd) ! saturated downward mass flux (mixed)      real, intent(out):: dnwd1(len, nd) ! saturated downward mass flux (mixed)
76      real, intent(out):: dnwd01(len, nd) ! unsaturated downward mass flux      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)
86    
# Line 130  contains Line 111  contains
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.
# Line 185  contains Line 159  contains
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).
# Line 215  contains Line 186  contains
186    
187      !  Local arrays      !  Local arrays
188    
     integer noff  
189      real da(len, nd), phi(len, nd, nd), mp(len, nd)      real da(len, nd), phi(len, nd, nd), mp(len, nd)
190    
191      integer i, k, n, il, j      integer i, k, il
192      integer icbmax      integer icbmax
193      integer nk1(klon)      integer nk1(klon)
194      integer icbs1(klon)      integer icbs1(klon)
# Line 227  contains Line 197  contains
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 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 340  contains Line 306  contains
306         end do         end do
307      end do      end do
308    
     do  j = 1, ntra  
        do  k = 1, nd  
           do  i = 1, len  
              ftra1(i, k, j) = 0.0  
           end do  
        end do  
     end do  
   
309      do  i = 1, len      do  i = 1, len
310         precip1(i) = 0.0         precip1(i) = 0.0
311         iflag1(i) = 0         iflag1(i) = 0
# 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 441  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, iflag1, nk1, icb1, &            CALL cv3_compress(len, nloc, ncum, nd, iflag1, nk1, icb1, icbs1, &
403                 icbs1, plcl1, tnk1, qnk1, gznk1, pbase1, buoybase1, t1, q1, &                 plcl1, tnk1, qnk1, gznk1, pbase1, buoybase1, t1, q1, qs1, u1, &
404                 qs1, u1, v1, gz1, th1, tra1, h1, lv1, cpn1, p1, ph1, tv1, tp1, &                 v1, gz1, th1, h1, lv1, cpn1, p1, ph1, tv1, tp1, tvp1, clw1, &
405                 tvp1, clw1, sig1, w01, iflag, nk, icb, icbs, plcl, tnk, qnk, &                 sig1, w01, iflag, nk, icb, icbs, plcl, tnk, qnk, gznk, pbase, &
406                 gznk, pbase, buoybase, t, q, qs, u, v, gz, th, tra, h, lv, &                 buoybase, t, q, qs, u, v, gz, th, h, lv, cpn, p, ph, tv, tp, &
407                 cpn, p, ph, tv, tp, tvp, clw, sig, w0)                 tvp, clw, sig, w0)
408         endif         endif
409    
410         if (iflag_con.eq.4) then         if (iflag_con.eq.4) then
# Line 506  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 524  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 544  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 584  contains Line 541  contains
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.96  
changed lines
  Added in v.97

  ViewVC Help
Powered by ViewVC 1.1.21