/[lmdze]/trunk/libf/phylmd/CV3_routines/cv3_feed.f90
ViewVC logotype

Annotation of /trunk/libf/phylmd/CV3_routines/cv3_feed.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 47 - (hide annotations)
Fri Jul 1 15:00:48 2011 UTC (12 years, 10 months ago) by guez
File size: 5514 byte(s)
Split "thermcell.f" and "cv3_routines.f".
Removed copies of files that are now in "L_util".
Moved "mva9" and "diagetpq" to their own files.
Unified variable names across procedures.

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

  ViewVC Help
Powered by ViewVC 1.1.21