/[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.f revision 47 by guez, Fri Jul 1 15:00:48 2011 UTC trunk/libf/phylmd/cv_driver.f90 revision 49 by guez, Wed Aug 24 11:43:14 2011 UTC
# Line 1  Line 1 
1  !  !
2  ! $Header: /home/cvsroot/LMDZ4/libf/phylmd/cv_driver.F,v 1.3 2005/04/15 12:36:17 lmdzadmin Exp $  ! $Header: /home/cvsroot/LMDZ4/libf/phylmd/cv_driver.F,v 1.3 2005/04/15 12:36:17 lmdzadmin Exp $
3  !  !
4        SUBROUTINE cv_driver(len,nd,ndp1,ntra,iflag_con,        SUBROUTINE cv_driver(len,nd,ndp1,ntra,iflag_con, &
5       &                   t1,q1,qs1,u1,v1,tra1,                           t1,q1,qs1,u1,v1,tra1, &
6       &                   p1,ph1,iflag1,ft1,fq1,fu1,fv1,ftra1,                           p1,ph1,iflag1,ft1,fq1,fu1,fv1,ftra1, &
7       &                   precip1,VPrecip1,                           precip1,VPrecip1, &
8       &                   cbmf1,sig1,w01,                           cbmf1,sig1,w01, &
9       &                   icb1,inb1,                           icb1,inb1, &
10       &                   delt,Ma1,upwd1,dnwd1,dnwd01,qcondc1,wd1,cape1,                           delt,Ma1,upwd1,dnwd1,dnwd01,qcondc1,wd1,cape1, &
11       &                   da1,phi1,mp1)                           da1,phi1,mp1)
12  C  !
13        use dimens_m        use dimens_m
14        use dimphy        use dimphy
15        implicit none        implicit none
16  C  !
17  C.............................START PROLOGUE............................  !.............................START PROLOGUE............................
18  C  !
19  C PARAMETERS:  ! PARAMETERS:
20  C      Name            Type         Usage            Description  !      Name            Type         Usage            Description
21  C   ----------      ----------     -------  ----------------------------  !   ----------      ----------     -------  ----------------------------
22  C  !
23  C      len           Integer        Input        first (i) dimension  !      len           Integer        Input        first (i) dimension
24  C      nd            Integer        Input        vertical (k) dimension  !      nd            Integer        Input        vertical (k) dimension
25  C      ndp1          Integer        Input        nd + 1  !      ndp1          Integer        Input        nd + 1
26  C      ntra          Integer        Input        number of tracors  !      ntra          Integer        Input        number of tracors
27  C      iflag_con     Integer        Input        version of convect (3/4)  !      iflag_con     Integer        Input        version of convect (3/4)
28  C      t1            Real           Input        temperature  !      t1            Real           Input        temperature
29  C      q1            Real           Input        specific hum  !      q1            Real           Input        specific hum
30  C      qs1           Real           Input        sat specific hum  !      qs1           Real           Input        sat specific hum
31  C      u1            Real           Input        u-wind  !      u1            Real           Input        u-wind
32  C      v1            Real           Input        v-wind  !      v1            Real           Input        v-wind
33  C      tra1          Real           Input        tracors  !      tra1          Real           Input        tracors
34  C      p1            Real           Input        full level pressure  !      p1            Real           Input        full level pressure
35  C      ph1           Real           Input        half level pressure  !      ph1           Real           Input        half level pressure
36  C      iflag1        Integer        Output       flag for Emanuel conditions  !      iflag1        Integer        Output       flag for Emanuel conditions
37  C      ft1           Real           Output       temp tend  !      ft1           Real           Output       temp tend
38  C      fq1           Real           Output       spec hum tend  !      fq1           Real           Output       spec hum tend
39  C      fu1           Real           Output       u-wind tend  !      fu1           Real           Output       u-wind tend
40  C      fv1           Real           Output       v-wind tend  !      fv1           Real           Output       v-wind tend
41  C      ftra1         Real           Output       tracor tend  !      ftra1         Real           Output       tracor tend
42  C      precip1       Real           Output       precipitation  !      precip1       Real           Output       precipitation
43  C      VPrecip1      Real           Output       vertical profile of precipitations  !      VPrecip1      Real           Output       vertical profile of precipitations
44  C      cbmf1         Real           Output       cloud base mass flux  !      cbmf1         Real           Output       cloud base mass flux
45  C      sig1          Real           In/Out       section adiabatic updraft  !      sig1          Real           In/Out       section adiabatic updraft
46  C      w01           Real           In/Out       vertical velocity within adiab updraft  !      w01           Real           In/Out       vertical velocity within adiab updraft
47  C      delt          Real           Input        time step  !      delt          Real           Input        time step
48  C      Ma1           Real           Output       mass flux adiabatic updraft  !      Ma1           Real           Output       mass flux adiabatic updraft
49  C      upwd1         Real           Output       total upward mass flux (adiab+mixed)  !      upwd1         Real           Output       total upward mass flux (adiab+mixed)
50  C      dnwd1         Real           Output       saturated downward mass flux (mixed)  !      dnwd1         Real           Output       saturated downward mass flux (mixed)
51  C      dnwd01        Real           Output       unsaturated downward mass flux  !      dnwd01        Real           Output       unsaturated downward mass flux
52  C      qcondc1       Real           Output       in-cld mixing ratio of condensed water  !      qcondc1       Real           Output       in-cld mixing ratio of condensed water
53  C      wd1           Real           Output       downdraft velocity scale for sfc fluxes  !      wd1           Real           Output       downdraft velocity scale for sfc fluxes
54  C      cape1         Real           Output       CAPE  !      cape1         Real           Output       CAPE
55  C  !
56  C S. Bony, Mar 2002:  ! S. Bony, Mar 2002:
57  C       * Several modules corresponding to different physical processes  !     * Several modules corresponding to different physical processes
58  C       * Several versions of convect may be used:  !     * Several versions of convect may be used:
59  C               - iflag_con=3: version lmd  (previously named convect3)  !        - iflag_con=3: version lmd  (previously named convect3)
60  C               - iflag_con=4: version 4.3b (vect. version, previously convect1/2)  !        - iflag_con=4: version 4.3b (vect. version, previously convect1/2)
61  C   + tard:     - iflag_con=5: version lmd with ice (previously named convectg)  !   + tard:    - iflag_con=5: version lmd with ice (previously named convectg)
62  C S. Bony, Oct 2002:  ! S. Bony, Oct 2002:
63  C       * Vectorization of convect3 (ie version lmd)  !     * Vectorization of convect3 (ie version lmd)
64  C  !
65  C..............................END PROLOGUE.............................  !..............................END PROLOGUE.............................
66  c  !
67  c  !
68    
69        integer len        integer len
70        integer nd        integer nd
# Line 94  c Line 94  c
94    
95        real qcondc1(len,nd)     ! cld        real qcondc1(len,nd)     ! cld
96        real wd1(len)            ! gust        real wd1(len)            ! gust
97        real cape1(len)            real cape1(len)
98    
99        real da1(len,nd),phi1(len,nd,nd),mp1(len,nd)        real da1(len,nd),phi1(len,nd,nd),mp1(len,nd)
100        real da(len,nd),phi(len,nd,nd),mp(len,nd)        real da(len,nd),phi(len,nd,nd),mp(len,nd)
# Line 212  c Line 212  c
212  !  det:   Array of detrainment mass flux of dimension ND.  !  det:   Array of detrainment mass flux of dimension ND.
213  !  !
214  !-------------------------------------------------------------------  !-------------------------------------------------------------------
215  c  !
216  c  Local arrays  !  Local arrays
217  c  !
218    
219        integer i,k,n,il,j        integer i,k,n,il,j
220        integer icbmax        integer icbmax
# Line 244  c Line 244  c
244        real sig1(klon,klev)        real sig1(klon,klev)
245        real w01(klon,klev)        real w01(klon,klev)
246        real th1(klon,klev)        real th1(klon,klev)
247  c  !
248        integer ncum        integer ncum
249  c  !
250  c (local) compressed fields:  ! (local) compressed fields:
251  c  !
252        integer nloc        integer nloc
253        parameter (nloc=klon) ! pour l'instant        parameter (nloc=klon) ! pour l'instant
254    
# Line 293  c Line 293  c
293  ! --- SET CONSTANTS AND PARAMETERS  ! --- SET CONSTANTS AND PARAMETERS
294  !-------------------------------------------------------------------  !-------------------------------------------------------------------
295    
296  c -- set simulation flags:  ! -- set simulation flags:
297  c   (common cvflag)  !   (common cvflag)
298    
299         CALL cv_flag         CALL cv_flag
300    
301  c -- set thermodynamical constants:  ! -- set thermodynamical constants:
302  c       (common cvthermo)  !     (common cvthermo)
303    
304         CALL cv_thermo(iflag_con)         CALL cv_thermo(iflag_con)
305    
306  c -- set convect parameters  ! -- set convect parameters
307  c  !
308  c       includes microphysical parameters and parameters that  !     includes microphysical parameters and parameters that
309  c       control the rate of approach to quasi-equilibrium)  !     control the rate of approach to quasi-equilibrium)
310  c       (common cvparam)  !     (common cvparam)
311    
312        if (iflag_con.eq.3) then        if (iflag_con.eq.3) then
313         CALL cv3_param(nd,delt)         CALL cv3_param(nd,delt)
# Line 330  c      (common cvparam) Line 330  c      (common cvparam)
330           tvp1(i,k)=0.0           tvp1(i,k)=0.0
331           tp1(i,k)=0.0           tp1(i,k)=0.0
332           clw1(i,k)=0.0           clw1(i,k)=0.0
333  cym  !ym
334           clw(i,k)=0.0               clw(i,k)=0.0
335           gz1(i,k) = 0.           gz1(i,k) = 0.
336           VPrecip1(i,k) = 0.           VPrecip1(i,k) = 0.
337           Ma1(i,k)=0.0           Ma1(i,k)=0.0
# Line 346  cym Line 346  cym
346         do 31 k=1,nd         do 31 k=1,nd
347          do 32 i=1,len          do 32 i=1,len
348           ftra1(i,k,j)=0.0           ftra1(i,k,j)=0.0
349   32     continue       32     continue
350   31    continue       31    continue
351   30   continue       30   continue
352    
353        do 60 i=1,len        do 60 i=1,len
354          precip1(i)=0.0          precip1(i)=0.0
# Line 370  cym Line 370  cym
370  !--------------------------------------------------------------------  !--------------------------------------------------------------------
371    
372        if (iflag_con.eq.3) then        if (iflag_con.eq.3) then
373         CALL cv3_prelim(len,nd,ndp1,t1,q1,p1,ph1            ! nd->na         CALL cv3_prelim(len,nd,ndp1,t1,q1,p1,ph1             &
374       o               ,lv1,cpn1,tv1,gz1,h1,hm1,th1)                       ,lv1,cpn1,tv1,gz1,h1,hm1,th1)! nd->na
375        endif        endif
376    
377        if (iflag_con.eq.4) then        if (iflag_con.eq.4) then
378         CALL cv_prelim(len,nd,ndp1,t1,q1,p1,ph1         CALL cv_prelim(len,nd,ndp1,t1,q1,p1,ph1 &
379       o               ,lv1,cpn1,tv1,gz1,h1,hm1)                       ,lv1,cpn1,tv1,gz1,h1,hm1)
380        endif        endif
381    
382  !--------------------------------------------------------------------  !--------------------------------------------------------------------
# Line 384  cym Line 384  cym
384  !--------------------------------------------------------------------  !--------------------------------------------------------------------
385    
386        if (iflag_con.eq.3) then        if (iflag_con.eq.3) then
387         CALL cv3_feed(len,nd,t1,q1,qs1,p1,ph1,hm1,gz1           ! nd->na         CALL cv3_feed(len,nd,t1,q1,qs1,p1,ph1,hm1,gz1            &
388       o         ,nk1,icb1,icbmax,iflag1,tnk1,qnk1,gznk1,plcl1)                 ,nk1,icb1,icbmax,iflag1,tnk1,qnk1,gznk1,plcl1) ! nd->na
389        endif        endif
390    
391        if (iflag_con.eq.4) then        if (iflag_con.eq.4) then
392         CALL cv_feed(len,nd,t1,q1,qs1,p1,hm1,gz1         CALL cv_feed(len,nd,t1,q1,qs1,p1,hm1,gz1 &
393       o         ,nk1,icb1,icbmax,iflag1,tnk1,qnk1,gznk1,plcl1)                 ,nk1,icb1,icbmax,iflag1,tnk1,qnk1,gznk1,plcl1)
394        endif        endif
395    
396  !--------------------------------------------------------------------  !--------------------------------------------------------------------
397  ! --- UNDILUTE (ADIABATIC) UPDRAFT / 1st part  ! --- UNDILUTE (ADIABATIC) UPDRAFT / 1st part
398  ! (up through ICB for convect4, up through ICB+1 for convect3)  ! (up through ICB for convect4, up through ICB+1 for convect3)
399  !     Calculates the lifted parcel virtual temperature at nk, the  !     Calculates the lifted parcel virtual temperature at nk, the
400  !     actual temperature, and the adiabatic liquid water content.  !     actual temperature, and the adiabatic liquid water content.
401  !--------------------------------------------------------------------  !--------------------------------------------------------------------
402    
403        if (iflag_con.eq.3) then        if (iflag_con.eq.3) then
404         CALL cv3_undilute1(len,nd,t1,q1,qs1,gz1,plcl1,p1,nk1,icb1  ! nd->na         CALL cv3_undilute1(len,nd,t1,q1,qs1,gz1,plcl1,p1,nk1,icb1   &
405       o                        ,tp1,tvp1,clw1,icbs1)                                ,tp1,tvp1,clw1,icbs1) ! nd->na
406        endif        endif
407    
408        if (iflag_con.eq.4) then        if (iflag_con.eq.4) then
409         CALL cv_undilute1(len,nd,t1,q1,qs1,gz1,p1,nk1,icb1,icbmax         CALL cv_undilute1(len,nd,t1,q1,qs1,gz1,p1,nk1,icb1,icbmax &
410       :                        ,tp1,tvp1,clw1)                                ,tp1,tvp1,clw1)
411        endif        endif
412    
413  !-------------------------------------------------------------------  !-------------------------------------------------------------------
# Line 415  cym Line 415  cym
415  !-------------------------------------------------------------------  !-------------------------------------------------------------------
416    
417        if (iflag_con.eq.3) then        if (iflag_con.eq.3) then
418         CALL cv3_trigger(len,nd,icb1,plcl1,p1,th1,tv1,tvp1      ! nd->na         CALL cv3_trigger(len,nd,icb1,plcl1,p1,th1,tv1,tvp1       &
419       o                 ,pbase1,buoybase1,iflag1,sig1,w01)                         ,pbase1,buoybase1,iflag1,sig1,w01) ! nd->na
420        endif        endif
421    
422        if (iflag_con.eq.4) then        if (iflag_con.eq.4) then
# Line 435  cym Line 435  cym
435          endif          endif
436   400  continue   400  continue
437    
438  c       print*,'klon, ncum = ',len,ncum  !       print*,'klon, ncum = ',len,ncum
439    
440        IF (ncum.gt.0) THEN        IF (ncum.gt.0) THEN
441    
442  !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^  !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
443  ! --- COMPRESS THE FIELDS  ! --- COMPRESS THE FIELDS
444  !               (-> vectorization over convective gridpoints)  !        (-> vectorization over convective gridpoints)
445  !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^  !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
446    
447        if (iflag_con.eq.3) then        if (iflag_con.eq.3) then
448         CALL cv3_compress( len,nloc,ncum,nd,ntra         CALL cv3_compress( len,nloc,ncum,nd,ntra &
449       :    ,iflag1,nk1,icb1,icbs1            ,iflag1,nk1,icb1,icbs1 &
450       :    ,plcl1,tnk1,qnk1,gznk1,pbase1,buoybase1            ,plcl1,tnk1,qnk1,gznk1,pbase1,buoybase1 &
451       :    ,t1,q1,qs1,u1,v1,gz1,th1            ,t1,q1,qs1,u1,v1,gz1,th1 &
452       :    ,tra1            ,tra1 &
453       :    ,h1,lv1,cpn1,p1,ph1,tv1,tp1,tvp1,clw1            ,h1,lv1,cpn1,p1,ph1,tv1,tp1,tvp1,clw1  &
454       :    ,sig1,w01            ,sig1,w01 &
455       o    ,iflag,nk,icb,icbs            ,iflag,nk,icb,icbs &
456       o    ,plcl,tnk,qnk,gznk,pbase,buoybase            ,plcl,tnk,qnk,gznk,pbase,buoybase &
457       o    ,t,q,qs,u,v,gz,th            ,t,q,qs,u,v,gz,th &
458       o    ,tra            ,tra &
459       o    ,h,lv,cpn,p,ph,tv,tp,tvp,clw            ,h,lv,cpn,p,ph,tv,tp,tvp,clw  &
460       o    ,sig,w0  )            ,sig,w0  )
461        endif        endif
462    
463        if (iflag_con.eq.4) then        if (iflag_con.eq.4) then
464         CALL cv_compress( len,nloc,ncum,nd         CALL cv_compress( len,nloc,ncum,nd &
465       :    ,iflag1,nk1,icb1            ,iflag1,nk1,icb1 &
466       :    ,cbmf1,plcl1,tnk1,qnk1,gznk1            ,cbmf1,plcl1,tnk1,qnk1,gznk1 &
467       :    ,t1,q1,qs1,u1,v1,gz1            ,t1,q1,qs1,u1,v1,gz1 &
468       :    ,h1,lv1,cpn1,p1,ph1,tv1,tp1,tvp1,clw1            ,h1,lv1,cpn1,p1,ph1,tv1,tp1,tvp1,clw1 &
469       o    ,iflag,nk,icb            ,iflag,nk,icb &
470       o    ,cbmf,plcl,tnk,qnk,gznk            ,cbmf,plcl,tnk,qnk,gznk &
471       o    ,t,q,qs,u,v,gz,h,lv,cpn,p,ph,tv,tp,tvp,clw            ,t,q,qs,u,v,gz,h,lv,cpn,p,ph,tv,tp,tvp,clw  &
472       o    ,dph )            ,dph )
473        endif        endif
474    
475  !-------------------------------------------------------------------  !-------------------------------------------------------------------
# Line 483  c       print*,'klon, ncum = ',len,ncum Line 483  c       print*,'klon, ncum = ',len,ncum
483  !-------------------------------------------------------------------  !-------------------------------------------------------------------
484    
485        if (iflag_con.eq.3) then        if (iflag_con.eq.3) then
486         CALL cv3_undilute2(nloc,ncum,nd,icb,icbs,nk        !na->nd         CALL cv3_undilute2(nloc,ncum,nd,icb,icbs,nk         &
487       :                        ,tnk,qnk,gznk,t,q,qs,gz                                ,tnk,qnk,gznk,t,q,qs,gz &
488       :                        ,p,h,tv,lv,pbase,buoybase,plcl                                ,p,h,tv,lv,pbase,buoybase,plcl &
489       o                        ,inb,tp,tvp,clw,hp,ep,sigp,buoy)                                ,inb,tp,tvp,clw,hp,ep,sigp,buoy) !na->nd
490        endif        endif
491    
492        if (iflag_con.eq.4) then        if (iflag_con.eq.4) then
493         CALL cv_undilute2(nloc,ncum,nd,icb,nk         CALL cv_undilute2(nloc,ncum,nd,icb,nk &
494       :                        ,tnk,qnk,gznk,t,q,qs,gz                                ,tnk,qnk,gznk,t,q,qs,gz &
495       :                        ,p,dph,h,tv,lv                                ,p,dph,h,tv,lv &
496       o             ,inb,inbis,tp,tvp,clw,hp,ep,sigp,frac)                     ,inb,inbis,tp,tvp,clw,hp,ep,sigp,frac)
497        endif        endif
498    
499  !-------------------------------------------------------------------  !-------------------------------------------------------------------
# Line 501  c       print*,'klon, ncum = ',len,ncum Line 501  c       print*,'klon, ncum = ',len,ncum
501  !-------------------------------------------------------------------  !-------------------------------------------------------------------
502    
503        if (iflag_con.eq.3) then        if (iflag_con.eq.3) then
504         CALL cv3_closure(nloc,ncum,nd,icb,inb              ! na->nd         CALL cv3_closure(nloc,ncum,nd,icb,inb               &
505       :                       ,pbase,p,ph,tv,buoy                               ,pbase,p,ph,tv,buoy &
506       o                       ,sig,w0,cape,m)                               ,sig,w0,cape,m) ! na->nd
507        endif        endif
508    
509        if (iflag_con.eq.4) then        if (iflag_con.eq.4) then
510         CALL cv_closure(nloc,ncum,nd,nk,icb         CALL cv_closure(nloc,ncum,nd,nk,icb &
511       :                ,tv,tvp,p,ph,dph,plcl,cpn                        ,tv,tvp,p,ph,dph,plcl,cpn &
512       o                ,iflag,cbmf)                        ,iflag,cbmf)
513        endif        endif
514    
515  !-------------------------------------------------------------------  !-------------------------------------------------------------------
# Line 517  c       print*,'klon, ncum = ',len,ncum Line 517  c       print*,'klon, ncum = ',len,ncum
517  !-------------------------------------------------------------------  !-------------------------------------------------------------------
518    
519        if (iflag_con.eq.3) then        if (iflag_con.eq.3) then
520         CALL cv3_mixing(nloc,ncum,nd,nd,ntra,icb,nk,inb    ! na->nd         CALL cv3_mixing(nloc,ncum,nd,nd,ntra,icb,nk,inb     &
521       :                     ,ph,t,q,qs,u,v,tra,h,lv,qnk                             ,ph,t,q,qs,u,v,tra,h,lv,qnk &
522       :                     ,hp,tv,tvp,ep,clw,m,sig                             ,hp,tv,tvp,ep,clw,m,sig &
523       o ,ment,qent,uent,vent, nent,sij,elij,ments,qents,traent)         ,ment,qent,uent,vent, nent,sij,elij,ments,qents,traent)! na->nd
524        endif        endif
525    
526        if (iflag_con.eq.4) then        if (iflag_con.eq.4) then
527         CALL cv_mixing(nloc,ncum,nd,icb,nk,inb,inbis         CALL cv_mixing(nloc,ncum,nd,icb,nk,inb,inbis &
528       :                     ,ph,t,q,qs,u,v,h,lv,qnk                             ,ph,t,q,qs,u,v,h,lv,qnk &
529       :                     ,hp,tv,tvp,ep,clw,cbmf                             ,hp,tv,tvp,ep,clw,cbmf &
530       o                     ,m,ment,qent,uent,vent,nent,sij,elij)                             ,m,ment,qent,uent,vent,nent,sij,elij)
531        endif        endif
532    
533  !-------------------------------------------------------------------  !-------------------------------------------------------------------
# Line 535  c       print*,'klon, ncum = ',len,ncum Line 535  c       print*,'klon, ncum = ',len,ncum
535  !-------------------------------------------------------------------  !-------------------------------------------------------------------
536    
537        if (iflag_con.eq.3) then        if (iflag_con.eq.3) then
538         CALL cv3_unsat(nloc,ncum,nd,nd,ntra,icb,inb    ! na->nd         CALL cv3_unsat(nloc,ncum,nd,nd,ntra,icb,inb     &
539       :               ,t,q,qs,gz,u,v,tra,p,ph                       ,t,q,qs,gz,u,v,tra,p,ph &
540       :               ,th,tv,lv,cpn,ep,sigp,clw                       ,th,tv,lv,cpn,ep,sigp,clw &
541       :               ,m,ment,elij,delt,plcl                       ,m,ment,elij,delt,plcl &
542       o          ,mp,qp,up,vp,trap,wt,water,evap,b)                  ,mp,qp,up,vp,trap,wt,water,evap,b)! na->nd
543        endif        endif
544    
545        if (iflag_con.eq.4) then        if (iflag_con.eq.4) then
546         CALL cv_unsat(nloc,ncum,nd,inb,t,q,qs,gz,u,v,p,ph         CALL cv_unsat(nloc,ncum,nd,inb,t,q,qs,gz,u,v,p,ph &
547       :                   ,h,lv,ep,sigp,clw,m,ment,elij                           ,h,lv,ep,sigp,clw,m,ment,elij &
548       o                   ,iflag,mp,qp,up,vp,wt,water,evap)                           ,iflag,mp,qp,up,vp,wt,water,evap)
549        endif        endif
550    
551  !-------------------------------------------------------------------  !-------------------------------------------------------------------
# Line 555  c       print*,'klon, ncum = ',len,ncum Line 555  c       print*,'klon, ncum = ',len,ncum
555  !-------------------------------------------------------------------  !-------------------------------------------------------------------
556    
557        if (iflag_con.eq.3) then        if (iflag_con.eq.3) then
558         CALL cv3_yield(nloc,ncum,nd,nd,ntra            ! na->nd         CALL cv3_yield(nloc,ncum,nd,nd,ntra             &
559       :                     ,icb,inb,delt                             ,icb,inb,delt &
560       :                     ,t,q,u,v,tra,gz,p,ph,h,hp,lv,cpn,th                             ,t,q,u,v,tra,gz,p,ph,h,hp,lv,cpn,th &
561       :                     ,ep,clw,m,tp,mp,qp,up,vp,trap                             ,ep,clw,m,tp,mp,qp,up,vp,trap &
562       :                     ,wt,water,evap,b                             ,wt,water,evap,b &
563       :                     ,ment,qent,uent,vent,nent,elij,traent,sig                             ,ment,qent,uent,vent,nent,elij,traent,sig &
564       :                     ,tv,tvp                             ,tv,tvp &
565       o                     ,iflag,precip,VPrecip,ft,fq,fu,fv,ftra                             ,iflag,precip,VPrecip,ft,fq,fu,fv,ftra &
566       o                     ,upwd,dnwd,dnwd0,ma,mike,tls,tps,qcondc,wd)                             ,upwd,dnwd,dnwd0,ma,mike,tls,tps,qcondc,wd)! na->nd
567        endif        endif
568    
569        if (iflag_con.eq.4) then        if (iflag_con.eq.4) then
570         CALL cv_yield(nloc,ncum,nd,nk,icb,inb,delt         CALL cv_yield(nloc,ncum,nd,nk,icb,inb,delt &
571       :              ,t,q,u,v,gz,p,ph,h,hp,lv,cpn                      ,t,q,u,v,gz,p,ph,h,hp,lv,cpn &
572       :              ,ep,clw,frac,m,mp,qp,up,vp                      ,ep,clw,frac,m,mp,qp,up,vp &
573       :              ,wt,water,evap                      ,wt,water,evap &
574       :              ,ment,qent,uent,vent,nent,elij                      ,ment,qent,uent,vent,nent,elij &
575       :              ,tv,tvp                      ,tv,tvp &
576       o              ,iflag,wd,qprime,tprime                      ,iflag,wd,qprime,tprime &
577       o              ,precip,cbmf,ft,fq,fu,fv,Ma,qcondc)                      ,precip,cbmf,ft,fq,fu,fv,Ma,qcondc)
578        endif        endif
579    
580  !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^  !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
# Line 582  c       print*,'klon, ncum = ',len,ncum Line 582  c       print*,'klon, ncum = ',len,ncum
582  !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^  !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
583    
584        if (iflag_con.eq.3) then        if (iflag_con.eq.3) then
585         CALL cv3_tracer(nloc,len,ncum,nd,nd,         CALL cv3_tracer(nloc,len,ncum,nd,nd, &
586       :                  ment,sij,da,phi)                          ment,sij,da,phi)
587        endif        endif
588    
589  !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^  !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
590  ! --- UNCOMPRESS THE FIELDS  ! --- UNCOMPRESS THE FIELDS
591  !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^  !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
592  c set iflag1 =42 for non convective points  ! set iflag1 =42 for non convective points
593        do  i=1,len        do  i=1,len
594          iflag1(i)=42          iflag1(i)=42
595        end do        end do
596  c  !
597        if (iflag_con.eq.3) then        if (iflag_con.eq.3) then
598         CALL cv3_uncompress(nloc,len,ncum,nd,ntra,idcum         CALL cv3_uncompress(nloc,len,ncum,nd,ntra,idcum &
599       :          ,iflag                  ,iflag &
600       :          ,precip,VPrecip,sig,w0                  ,precip,VPrecip,sig,w0 &
601       :          ,ft,fq,fu,fv,ftra                  ,ft,fq,fu,fv,ftra &
602       :          ,inb                  ,inb  &
603       :          ,Ma,upwd,dnwd,dnwd0,qcondc,wd,cape                  ,Ma,upwd,dnwd,dnwd0,qcondc,wd,cape &
604       :          ,da,phi,mp                  ,da,phi,mp &
605       o          ,iflag1                  ,iflag1 &
606       o          ,precip1,VPrecip1,sig1,w01                  ,precip1,VPrecip1,sig1,w01 &
607       o          ,ft1,fq1,fu1,fv1,ftra1                  ,ft1,fq1,fu1,fv1,ftra1 &
608       o          ,inb1                  ,inb1 &
609       o          ,Ma1,upwd1,dnwd1,dnwd01,qcondc1,wd1,cape1                  ,Ma1,upwd1,dnwd1,dnwd01,qcondc1,wd1,cape1  &
610       o          ,da1,phi1,mp1)                  ,da1,phi1,mp1)
611        endif        endif
612    
613        if (iflag_con.eq.4) then        if (iflag_con.eq.4) then
614         CALL cv_uncompress(nloc,len,ncum,nd,idcum         CALL cv_uncompress(nloc,len,ncum,nd,idcum &
615       :          ,iflag                  ,iflag &
616       :          ,precip,cbmf                  ,precip,cbmf &
617       :          ,ft,fq,fu,fv                  ,ft,fq,fu,fv &
618       :          ,Ma,qcondc                              ,Ma,qcondc             &
619       o          ,iflag1                  ,iflag1 &
620       o          ,precip1,cbmf1                  ,precip1,cbmf1 &
621       o          ,ft1,fq1,fu1,fv1                  ,ft1,fq1,fu1,fv1 &
622       o          ,Ma1,qcondc1 )                            ,Ma1,qcondc1 )
623        endif        endif
624    
625        ENDIF ! ncum>0        ENDIF ! ncum>0
# Line 628  c Line 628  c
628    
629        return        return
630        end        end
   
 !==================================================================  
       SUBROUTINE cv_flag  
             use cvflag  
       implicit none  
   
   
 c -- si .TRUE., on rend la gravite plus explicite et eventuellement  
 c differente de 10.0 dans convect3:  
       cvflag_grav = .TRUE.  
   
       return  
       end  
   
 !==================================================================  
       SUBROUTINE cv_thermo(iflag_con)  
       use SUPHEC_M  
             use cvthermo  
           implicit none  
   
 c-------------------------------------------------------------  
 c Set thermodynamical constants for convectL  
 c-------------------------------------------------------------  
   
   
       integer, intent(in):: iflag_con  
   
   
 c original set from convect:  
       if (iflag_con.eq.4) then  
        cpd=1005.7  
        cpv=1870.0  
        cl=4190.0  
        rrv=461.5  
        rrd=287.04  
        lv0=2.501E6  
        g=9.8  
        t0=273.15  
        grav=g  
       endif  
   
 c constants consistent with LMDZ:  
       if (iflag_con.eq.3) then  
        cpd = RCPD  
        cpv = RCPV  
        cl  = RCW  
        rrv = RV  
        rrd = RD  
        lv0 = RLVTT  
        g   = RG     ! not used in convect3  
 c ori      t0  = RTT  
        t0  = 273.15 ! convect3 (RTT=273.16)  
 c maf       grav= 10.    ! implicitely or explicitely used in convect3  
        grav= g    ! implicitely or explicitely used in convect3  
       endif  
   
       rowl=1000.0 !(a quelle variable de SUPHEC_M cela correspond-il?)  
   
       clmcpv=cl-cpv  
       clmcpd=cl-cpd  
       cpdmcp=cpd-cpv  
       cpvmcpd=cpv-cpd  
       cpvmcl=cl-cpv ! for convect3  
       eps=rrd/rrv  
       epsi=1.0/eps  
       epsim1=epsi-1.0  
 c      ginv=1.0/g  
       ginv=1.0/grav  
       hrd=0.5*rrd  
   
       return  
       end  
   

Legend:
Removed from v.47  
changed lines
  Added in v.49

  ViewVC Help
Powered by ViewVC 1.1.21