/[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

trunk/libf/phylmd/cv_driver.f90 revision 69 by guez, Mon Feb 18 16:33:12 2013 UTC trunk/phylmd/cv_driver.f revision 91 by guez, Wed Mar 26 17:18:58 2014 UTC
# Line 9  contains Line 9  contains
9         sig1, w01, icb1, inb1, delt, Ma1, upwd1, dnwd1, dnwd01, qcondc1, wd1, &         sig1, w01, icb1, inb1, delt, Ma1, upwd1, dnwd1, dnwd01, qcondc1, wd1, &
10         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      ! Main driver for convection
15    
16        ! S. Bony, March 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      use clesphys2, only: iflag_con
31        use cv3_compress_m, only: cv3_compress
32      use cv3_param_m, only: cv3_param      use cv3_param_m, only: cv3_param
33      USE dimphy, ONLY: klev, klon      USE dimphy, ONLY: klev, klon
34    
# Line 42  contains Line 57  contains
57      !      precip1       Real           Output       precipitation      !      precip1       Real           Output       precipitation
58      !      VPrecip1      Real           Output       vertical profile of precipitations      !      VPrecip1      Real           Output       vertical profile of precipitations
59      !      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  
60      !      delt          Real           Input        time step      !      delt          Real           Input        time step
61      !      Ma1           Real           Output       mass flux adiabatic updraft      !      Ma1           Real           Output       mass flux adiabatic updraft
62      !      qcondc1       Real           Output       in-cld mixing ratio of condensed water      !      qcondc1       Real           Output       in-cld mixing ratio of condensed water
63      !      wd1           Real           Output       downdraft velocity scale for sfc fluxes      !      wd1           Real           Output       downdraft velocity scale for sfc fluxes
64      !      cape1         Real           Output       CAPE      !      cape1         Real           Output       CAPE
65    
     ! 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)  
   
66      integer len      integer len
67      integer nd      integer nd
68      integer ndp1      integer ndp1
     integer noff  
69      integer, intent(in):: ntra      integer, intent(in):: ntra
70      real, intent(in):: t1(len, nd)      real, intent(in):: t1(len, nd)
71      real q1(len, nd)      real q1(len, nd)
72      real qs1(len, nd)      real qs1(len, nd)
73      real u1(len, nd)      real, intent(in):: u1(len, nd)
74      real v1(len, nd)      real, intent(in):: v1(len, nd)
75        real, intent(in):: tra1(len, nd, ntra)
76      real p1(len, nd)      real p1(len, nd)
77      real ph1(len, ndp1)      real ph1(len, ndp1)
78      integer iflag1(len)      integer iflag1(len)
# Line 76  contains Line 80  contains
80      real fq1(len, nd)      real fq1(len, nd)
81      real fu1(len, nd)      real fu1(len, nd)
82      real fv1(len, nd)      real fv1(len, nd)
83        real ftra1(len, nd, ntra)
84      real precip1(len)      real precip1(len)
     real cbmf1(len)  
85      real VPrecip1(len, nd+1)      real VPrecip1(len, nd+1)
86        real cbmf1(len)
87        real, intent(inout):: sig1(klon, klev) ! section adiabatic updraft
88    
89        real, intent(inout):: w01(klon, klev)
90        ! vertical velocity within adiabatic updraft
91    
92        integer icb1(klon)
93        integer inb1(klon)
94        real, intent(in):: delt
95      real Ma1(len, nd)      real Ma1(len, nd)
96      real, intent(out):: upwd1(len, nd) ! total upward mass flux (adiab+mixed)      real, intent(out):: upwd1(len, nd) ! total upward mass flux (adiab+mixed)
97      real, intent(out):: dnwd1(len, nd) ! saturated downward mass flux (mixed)      real, intent(out):: dnwd1(len, nd) ! saturated downward mass flux (mixed)
# Line 89  contains Line 102  contains
102      real cape1(len)      real cape1(len)
103    
104      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  
105    
106      !-------------------------------------------------------------------      !-------------------------------------------------------------------
107      ! --- ARGUMENTS      ! --- ARGUMENTS
# Line 207  contains Line 215  contains
215    
216      !  Local arrays      !  Local arrays
217    
218        integer noff
219        real da(len, nd), phi(len, nd, nd), mp(len, nd)
220    
221      integer i, k, n, il, j      integer i, k, n, il, j
222      integer icbmax      integer icbmax
223      integer nk1(klon)      integer nk1(klon)
     integer icb1(klon)  
     integer inb1(klon)  
224      integer icbs1(klon)      integer icbs1(klon)
225    
226      real plcl1(klon)      real plcl1(klon)
# Line 232  contains Line 241  contains
241      real tp1(klon, klev)      real tp1(klon, klev)
242      real tvp1(klon, klev)      real tvp1(klon, klev)
243      real clw1(klon, klev)      real clw1(klon, klev)
     real sig1(klon, klev)  
     real w01(klon, klev)  
244      real th1(klon, klev)      real th1(klon, klev)
245    
246      integer ncum      integer ncum
# Line 241  contains Line 248  contains
248      ! (local) compressed fields:      ! (local) compressed fields:
249    
250      integer nloc      integer nloc
251      parameter (nloc=klon) ! pour l'instant      parameter (nloc = klon) ! pour l'instant
252    
253      integer idcum(nloc)      integer idcum(nloc)
254      integer iflag(nloc), nk(nloc), icb(nloc)      integer iflag(nloc), nk(nloc), icb(nloc)
# Line 312  contains Line 319  contains
319      ! --- INITIALIZE OUTPUT ARRAYS AND PARAMETERS      ! --- INITIALIZE OUTPUT ARRAYS AND PARAMETERS
320      !---------------------------------------------------------------------      !---------------------------------------------------------------------
321    
322      do k=1, nd      do k = 1, nd
323         do  i=1, len         do  i = 1, len
324            ft1(i, k)=0.0            ft1(i, k) = 0.0
325            fq1(i, k)=0.0            fq1(i, k) = 0.0
326            fu1(i, k)=0.0            fu1(i, k) = 0.0
327            fv1(i, k)=0.0            fv1(i, k) = 0.0
328            tvp1(i, k)=0.0            tvp1(i, k) = 0.0
329            tp1(i, k)=0.0            tp1(i, k) = 0.0
330            clw1(i, k)=0.0            clw1(i, k) = 0.0
331            !ym            !ym
332            clw(i, k)=0.0            clw(i, k) = 0.0
333            gz1(i, k) = 0.            gz1(i, k)  =  0.
334            VPrecip1(i, k) = 0.            VPrecip1(i, k) = 0.
335            Ma1(i, k)=0.0            Ma1(i, k) = 0.0
336            upwd1(i, k)=0.0            upwd1(i, k) = 0.0
337            dnwd1(i, k)=0.0            dnwd1(i, k) = 0.0
338            dnwd01(i, k)=0.0            dnwd01(i, k) = 0.0
339            qcondc1(i, k)=0.0            qcondc1(i, k) = 0.0
340         end do         end do
341      end do      end do
342    
343      do  j=1, ntra      do  j = 1, ntra
344         do  k=1, nd         do  k = 1, nd
345            do  i=1, len            do  i = 1, len
346               ftra1(i, k, j)=0.0               ftra1(i, k, j) = 0.0
347            end do            end do
348         end do         end do
349      end do      end do
350    
351      do  i=1, len      do  i = 1, len
352         precip1(i)=0.0         precip1(i) = 0.0
353         iflag1(i)=0         iflag1(i) = 0
354         wd1(i)=0.0         wd1(i) = 0.0
355         cape1(i)=0.0         cape1(i) = 0.0
356         VPrecip1(i, nd+1)=0.0         VPrecip1(i, nd+1) = 0.0
357      end do      end do
358    
359      if (iflag_con.eq.3) then      if (iflag_con.eq.3) then
360         do il=1, len         do il = 1, len
361            sig1(il, nd)=sig1(il, nd)+1.            sig1(il, nd) = sig1(il, nd) + 1.
362            sig1(il, nd)=amin1(sig1(il, nd), 12.1)            sig1(il, nd)  =  min(sig1(il, nd), 12.1)
363         enddo         enddo
364      endif      endif
365    
# Line 406  contains Line 413  contains
413      !-------------------------------------------------------------------      !-------------------------------------------------------------------
414    
415      if (iflag_con.eq.3) then      if (iflag_con.eq.3) then
416         CALL cv3_trigger(len, nd, icb1, plcl1, p1, th1, tv1, tvp1       &         CALL cv3_trigger(len, nd, icb1, plcl1, p1, th1, tv1, tvp1, pbase1, &
417              , pbase1, buoybase1, iflag1, sig1, w01) ! nd->na              buoybase1, iflag1, sig1, w01) ! nd->na
418      endif      endif
419    
420      if (iflag_con.eq.4) then      if (iflag_con.eq.4) then
421         CALL cv_trigger(len, nd, icb1, cbmf1, tv1, tvp1, iflag1)         CALL cv_trigger(len, nd, icb1, cbmf1, tv1, tvp1, iflag1)
422      endif      endif
423    
     !=====================================================================  
424      ! --- IF THIS POINT IS REACHED, MOIST CONVECTIVE ADJUSTMENT IS NECESSARY      ! --- IF THIS POINT IS REACHED, MOIST CONVECTIVE ADJUSTMENT IS NECESSARY
     !=====================================================================  
425    
426      ncum=0      ncum = 0
427      do  i=1, len      do  i = 1, len
428         if(iflag1(i).eq.0)then         if(iflag1(i).eq.0)then
429            ncum=ncum+1            ncum = ncum+1
430            idcum(ncum)=i            idcum(ncum) = i
431         endif         endif
432      end do      end do
433    
# Line 436  contains Line 441  contains
441         !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^         !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
442    
443         if (iflag_con.eq.3) then         if (iflag_con.eq.3) then
444            CALL cv3_compress( len, nloc, ncum, nd, ntra &            CALL cv3_compress(len, nloc, ncum, nd, ntra, iflag1, nk1, icb1, &
445                 , iflag1, nk1, icb1, icbs1 &                 icbs1, plcl1, tnk1, qnk1, gznk1, pbase1, buoybase1, t1, q1, &
446                 , plcl1, tnk1, qnk1, gznk1, pbase1, buoybase1 &                 qs1, u1, v1, gz1, th1, tra1, h1, lv1, cpn1, p1, ph1, tv1, tp1, &
447                 , t1, q1, qs1, u1, v1, gz1, th1 &                 tvp1, clw1, sig1, w01, iflag, nk, icb, icbs, plcl, tnk, qnk, &
448                 , tra1 &                 gznk, pbase, buoybase, t, q, qs, u, v, gz, th, tra, h, lv, &
449                 , 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  )  
450         endif         endif
451    
452         if (iflag_con.eq.4) then         if (iflag_con.eq.4) then
# Line 580  contains Line 578  contains
578         !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^         !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
579         ! --- UNCOMPRESS THE FIELDS         ! --- UNCOMPRESS THE FIELDS
580         !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^         !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
581         ! set iflag1 =42 for non convective points         ! set iflag1  = 42 for non convective points
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

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

  ViewVC Help
Powered by ViewVC 1.1.21