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

Contents of /trunk/libf/phylmd/CV_routines/cv_feed.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: 3804 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_feed(len,nd,t,q,qs,p,hm,gz &
3 ,nk,icb,icbmax,iflag,tnk,qnk,gznk,plcl)
4 use cvparam
5 implicit none
6
7 !================================================================
8 ! Purpose: CONVECTIVE FEED
9 !================================================================
10
11
12 ! inputs:
13 integer len, nd
14 real, intent(in):: t(len,nd)
15 real q(len,nd), qs(len,nd), p(len,nd)
16 real hm(len,nd), gz(len,nd)
17
18 ! outputs:
19 integer iflag(len), nk(len), icb(len), icbmax
20 real tnk(len), qnk(len), gznk(len), plcl(len)
21
22 ! local variables:
23 integer i, k
24 integer ihmin(len)
25 real work(len)
26 real pnk(len), qsnk(len), rh(len), chi(len)
27
28 !-------------------------------------------------------------------
29 ! --- Find level of minimum moist static energy
30 ! --- If level of minimum moist static energy coincides with
31 ! --- or is lower than minimum allowable parcel origin level,
32 ! --- set iflag to 6.
33 !-------------------------------------------------------------------
34
35 do 180 i=1,len
36 work(i)=1.0e12
37 ihmin(i)=nl
38 180 continue
39 do 200 k=2,nlp
40 do 190 i=1,len
41 if((hm(i,k).lt.work(i)).and. &
42 (hm(i,k).lt.hm(i,k-1)))then
43 work(i)=hm(i,k)
44 ihmin(i)=k
45 endif
46 190 continue
47 200 continue
48 do 210 i=1,len
49 ihmin(i)=min(ihmin(i),nlm)
50 if(ihmin(i).le.minorig)then
51 iflag(i)=6
52 endif
53 210 continue
54 !
55 !-------------------------------------------------------------------
56 ! --- Find that model level below the level of minimum moist static
57 ! --- energy that has the maximum value of moist static energy
58 !-------------------------------------------------------------------
59
60 do 220 i=1,len
61 work(i)=hm(i,minorig)
62 nk(i)=minorig
63 220 continue
64 do 240 k=minorig+1,nl
65 do 230 i=1,len
66 if((hm(i,k).gt.work(i)).and.(k.le.ihmin(i)))then
67 work(i)=hm(i,k)
68 nk(i)=k
69 endif
70 230 continue
71 240 continue
72 !-------------------------------------------------------------------
73 ! --- Check whether parcel level temperature and specific humidity
74 ! --- are reasonable
75 !-------------------------------------------------------------------
76 do 250 i=1,len
77 if(((t(i,nk(i)).lt.250.0).or. &
78 (q(i,nk(i)).le.0.0).or. &
79 (p(i,ihmin(i)).lt.400.0)).and. &
80 (iflag(i).eq.0))iflag(i)=7
81 250 continue
82 !-------------------------------------------------------------------
83 ! --- Calculate lifted condensation level of air at parcel origin level
84 ! --- (Within 0.2% of formula of Bolton, MON. WEA. REV.,1980)
85 !-------------------------------------------------------------------
86 do 260 i=1,len
87 tnk(i)=t(i,nk(i))
88 qnk(i)=q(i,nk(i))
89 gznk(i)=gz(i,nk(i))
90 pnk(i)=p(i,nk(i))
91 qsnk(i)=qs(i,nk(i))
92 !
93 rh(i)=qnk(i)/qsnk(i)
94 rh(i)=min(1.0,rh(i))
95 chi(i)=tnk(i)/(1669.0-122.0*rh(i)-tnk(i))
96 plcl(i)=pnk(i)*(rh(i)**chi(i))
97 if(((plcl(i).lt.200.0).or.(plcl(i).ge.2000.0)) &
98 .and.(iflag(i).eq.0))iflag(i)=8
99 260 continue
100 !-------------------------------------------------------------------
101 ! --- Calculate first level above lcl (=icb)
102 !-------------------------------------------------------------------
103 do 270 i=1,len
104 icb(i)=nlm
105 270 continue
106 !
107 do 290 k=minorig,nl
108 do 280 i=1,len
109 if((k.ge.(nk(i)+1)).and.(p(i,k).lt.plcl(i))) &
110 icb(i)=min(icb(i),k)
111 280 continue
112 290 continue
113 !
114 do 300 i=1,len
115 if((icb(i).ge.nlm).and.(iflag(i).eq.0))iflag(i)=9
116 300 continue
117 !
118 ! Compute icbmax.
119 !
120 icbmax=2
121 do 310 i=1,len
122 icbmax=max(icbmax,icb(i))
123 310 continue
124
125 return
126 end

  ViewVC Help
Powered by ViewVC 1.1.21