/[lmdze]/trunk/libf/phylmd/CV_routines/cv_closure.f90
ViewVC logotype

Contents of /trunk/libf/phylmd/CV_routines/cv_closure.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 52 - (show annotations)
Fri Sep 23 12:28:01 2011 UTC (12 years, 7 months ago) by guez
File size: 2641 byte(s)
Split "conflx.f" into single-procedure files in directory "Conflx".

Split "cv_routines.f" into single-procedure files in directory
"CV_routines". Made module "cvparam" from included file
"cvparam.h". No included file other than "netcdf.inc" left in LMDZE.

1 !
2 SUBROUTINE cv_closure(nloc,ncum,nd,nk,icb &
3 ,tv,tvp,p,ph,dph,plcl,cpn &
4 ,iflag,cbmf)
5 use cvthermo
6 use cvparam
7 implicit none
8
9 ! inputs:
10 integer ncum, nd, nloc
11 integer nk(nloc), icb(nloc)
12 real tv(nloc,nd), tvp(nloc,nd), p(nloc,nd), dph(nloc,nd)
13 real ph(nloc,nd+1) ! caution nd instead ndp1 to be consistent...
14 real plcl(nloc), cpn(nloc,nd)
15
16 ! outputs:
17 integer iflag(nloc)
18 real cbmf(nloc) ! also an input
19
20 ! local variables:
21 integer i, k, icbmax
22 real dtpbl(nloc), dtmin(nloc), tvpplcl(nloc), tvaplcl(nloc)
23 real work(nloc)
24
25
26 !-------------------------------------------------------------------
27 ! Compute icbmax.
28 !-------------------------------------------------------------------
29
30 icbmax=2
31 do 230 i=1,ncum
32 icbmax=max(icbmax,icb(i))
33 230 continue
34
35 !=====================================================================
36 ! --- CALCULATE CLOUD BASE MASS FLUX
37 !=====================================================================
38 !
39 ! tvpplcl = parcel temperature lifted adiabatically from level
40 ! icb-1 to the LCL.
41 ! tvaplcl = virtual temperature at the LCL.
42 !
43 do 610 i=1,ncum
44 dtpbl(i)=0.0
45 tvpplcl(i)=tvp(i,icb(i)-1) &
46 -rrd*tvp(i,icb(i)-1)*(p(i,icb(i)-1)-plcl(i)) &
47 /(cpn(i,icb(i)-1)*p(i,icb(i)-1))
48 tvaplcl(i)=tv(i,icb(i)) &
49 +(tvp(i,icb(i))-tvp(i,icb(i)+1))*(plcl(i)-p(i,icb(i))) &
50 /(p(i,icb(i))-p(i,icb(i)+1))
51 610 continue
52
53 !-------------------------------------------------------------------
54 ! --- Interpolate difference between lifted parcel and
55 ! --- environmental temperatures to lifted condensation level
56 !-------------------------------------------------------------------
57 !
58 ! dtpbl = average of tvp-tv in the PBL (k=nk to icb-1).
59 !
60 do 630 k=minorig,icbmax
61 do 620 i=1,ncum
62 if((k.ge.nk(i)).and.(k.le.(icb(i)-1)))then
63 dtpbl(i)=dtpbl(i)+(tvp(i,k)-tv(i,k))*dph(i,k)
64 endif
65 620 continue
66 630 continue
67 do 640 i=1,ncum
68 dtpbl(i)=dtpbl(i)/(ph(i,nk(i))-ph(i,icb(i)))
69 dtmin(i)=tvpplcl(i)-tvaplcl(i)+dtmax+dtpbl(i)
70 640 continue
71 !
72 !-------------------------------------------------------------------
73 ! --- Adjust cloud base mass flux
74 !-------------------------------------------------------------------
75 !
76 do 650 i=1,ncum
77 work(i)=cbmf(i)
78 cbmf(i)=max(0.0,(1.0-damp)*cbmf(i)+0.1*alpha*dtmin(i))
79 if((work(i).eq.0.0).and.(cbmf(i).eq.0.0))then
80 iflag(i)=3
81 endif
82 650 continue
83
84 return
85 end

  ViewVC Help
Powered by ViewVC 1.1.21