/[lmdze]/trunk/phylmd/CV3_routines/cv3_feed.f
ViewVC logotype

Annotation of /trunk/phylmd/CV3_routines/cv3_feed.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 82 - (hide annotations)
Wed Mar 5 14:57:53 2014 UTC (10 years, 2 months ago) by guez
File size: 5541 byte(s)
Changed all ".f90" suffixes to ".f".
1 guez 47
2     SUBROUTINE cv3_feed(len,nd,t,q,qs,p,ph,hm,gz &
3     ,nk,icb,icbmax,iflag,tnk,qnk,gznk,plcl)
4 guez 69 use cv3_param_m
5 guez 47 implicit none
6    
7     !================================================================
8     ! Purpose: CONVECTIVE FEED
9     !
10     ! Main differences with cv_feed:
11     ! - ph added in input
12     ! - here, nk(i)=minorig
13     ! - icb defined differently (plcl compared with ph instead of p)
14     !
15     ! Main differences with convect3:
16     ! - we do not compute dplcldt and dplcldr of CLIFT anymore
17     ! - values iflag different (but tests identical)
18     ! - A,B explicitely defined (!...)
19     !================================================================
20    
21    
22     ! inputs:
23     integer len, nd
24 guez 52 real, intent(in):: t(len,nd)
25     real q(len,nd), qs(len,nd), p(len,nd)
26 guez 47 real hm(len,nd), gz(len,nd)
27     real ph(len,nd+1)
28    
29     ! outputs:
30     integer iflag(len), nk(len), icb(len), icbmax
31     real tnk(len), qnk(len), gznk(len), plcl(len)
32    
33     ! local variables:
34     integer i, k
35     integer ihmin(len)
36     real work(len)
37     real pnk(len), qsnk(len), rh(len), chi(len)
38     real A, B ! convect3
39     !ym
40     plcl=0.0
41     !@ !-------------------------------------------------------------------
42     !@ ! --- Find level of minimum moist static energy
43     !@ ! --- If level of minimum moist static energy coincides with
44     !@ ! --- or is lower than minimum allowable parcel origin level,
45     !@ ! --- set iflag to 6.
46     !@ !-------------------------------------------------------------------
47     !@
48     !@ do 180 i=1,len
49     !@ work(i)=1.0e12
50     !@ ihmin(i)=nl
51     !@ 180 continue
52     !@ do 200 k=2,nlp
53     !@ do 190 i=1,len
54     !@ if((hm(i,k).lt.work(i)).and.
55     !@ & (hm(i,k).lt.hm(i,k-1)))then
56     !@ work(i)=hm(i,k)
57     !@ ihmin(i)=k
58     !@ endif
59     !@ 190 continue
60     !@ 200 continue
61     !@ do 210 i=1,len
62     !@ ihmin(i)=min(ihmin(i),nlm)
63     !@ if(ihmin(i).le.minorig)then
64     !@ iflag(i)=6
65     !@ endif
66     !@ 210 continue
67     !@ c
68     !@ !-------------------------------------------------------------------
69     !@ ! --- Find that model level below the level of minimum moist static
70     !@ ! --- energy that has the maximum value of moist static energy
71     !@ !-------------------------------------------------------------------
72     !@
73     !@ do 220 i=1,len
74     !@ work(i)=hm(i,minorig)
75     !@ nk(i)=minorig
76     !@ 220 continue
77     !@ do 240 k=minorig+1,nl
78     !@ do 230 i=1,len
79     !@ if((hm(i,k).gt.work(i)).and.(k.le.ihmin(i)))then
80     !@ work(i)=hm(i,k)
81     !@ nk(i)=k
82     !@ endif
83     !@ 230 continue
84     !@ 240 continue
85    
86     !-------------------------------------------------------------------
87     ! --- Origin level of ascending parcels for convect3:
88     !-------------------------------------------------------------------
89    
90     do 220 i=1,len
91     nk(i)=minorig
92     220 continue
93    
94     !-------------------------------------------------------------------
95     ! --- Check whether parcel level temperature and specific humidity
96     ! --- are reasonable
97     !-------------------------------------------------------------------
98     do 250 i=1,len
99     if( ( ( t(i,nk(i)).lt.250.0 ) &
100     .or.( q(i,nk(i)).le.0.0 ) ) &
101     .and. &
102     ( iflag(i).eq.0) ) iflag(i)=7
103     250 continue
104     !-------------------------------------------------------------------
105     ! --- Calculate lifted condensation level of air at parcel origin level
106     ! --- (Within 0.2% of formula of Bolton, MON. WEA. REV.,1980)
107     !-------------------------------------------------------------------
108    
109     A = 1669.0 ! convect3
110     B = 122.0 ! convect3
111    
112     do 260 i=1,len
113    
114     if (iflag(i).ne.7) then ! modif sb Jun7th 2002
115    
116     tnk(i)=t(i,nk(i))
117     qnk(i)=q(i,nk(i))
118     gznk(i)=gz(i,nk(i))
119     pnk(i)=p(i,nk(i))
120     qsnk(i)=qs(i,nk(i))
121     !
122     rh(i)=qnk(i)/qsnk(i)
123     ! ori rh(i)=min(1.0,rh(i)) ! removed for convect3
124     ! ori chi(i)=tnk(i)/(1669.0-122.0*rh(i)-tnk(i))
125     chi(i)=tnk(i)/(A-B*rh(i)-tnk(i)) ! convect3
126     plcl(i)=pnk(i)*(rh(i)**chi(i))
127     if(((plcl(i).lt.200.0).or.(plcl(i).ge.2000.0)) &
128     .and.(iflag(i).eq.0))iflag(i)=8
129    
130     endif ! iflag=7
131    
132     260 continue
133    
134     !-------------------------------------------------------------------
135     ! --- Calculate first level above lcl (=icb)
136     !-------------------------------------------------------------------
137    
138     !@ do 270 i=1,len
139     !@ icb(i)=nlm
140     !@ 270 continue
141     !@c
142     !@ do 290 k=minorig,nl
143     !@ do 280 i=1,len
144     !@ if((k.ge.(nk(i)+1)).and.(p(i,k).lt.plcl(i)))
145     !@ & icb(i)=min(icb(i),k)
146     !@ 280 continue
147     !@ 290 continue
148     !@c
149     !@ do 300 i=1,len
150     !@ if((icb(i).ge.nlm).and.(iflag(i).eq.0))iflag(i)=9
151     !@ 300 continue
152    
153     do 270 i=1,len
154     icb(i)=nlm
155     270 continue
156     !
157     ! la modification consiste a comparer plcl a ph et non a p:
158     ! icb est defini par : ph(icb)<plcl<ph(icb-1)
159     !@ do 290 k=minorig,nl
160     do 290 k=3,nl-1 ! modif pour que icb soit sup/egal a 2
161     do 280 i=1,len
162     if( ph(i,k).lt.plcl(i) ) icb(i)=min(icb(i),k)
163     280 continue
164     290 continue
165     !
166     do 300 i=1,len
167     !@ if((icb(i).ge.nlm).and.(iflag(i).eq.0))iflag(i)=9
168     if((icb(i).eq.nlm).and.(iflag(i).eq.0))iflag(i)=9
169     300 continue
170    
171     do 400 i=1,len
172     icb(i) = icb(i)-1 ! icb sup ou egal a 2
173     400 continue
174     !
175     ! Compute icbmax.
176     !
177     icbmax=2
178     do 310 i=1,len
179     !! icbmax=max(icbmax,icb(i))
180     if (iflag(i).lt.7) icbmax=max(icbmax,icb(i)) ! sb Jun7th02
181     310 continue
182    
183     return
184     end

  ViewVC Help
Powered by ViewVC 1.1.21