/[MITgcm]/MITgcm/pkg/aim/phy_convmf.F
ViewVC logotype

Annotation of /MITgcm/pkg/aim/phy_convmf.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.3 - (hide annotations) (download)
Tue May 29 19:28:53 2001 UTC (23 years, 1 month ago) by cnh
Branch: MAIN
CVS Tags: checkpoint40pre1, checkpoint40pre2, checkpoint40pre5, checkpoint40pre6, checkpoint40pre8, checkpoint40pre4, checkpoint40pre3, checkpoint40pre9, checkpoint40pre7, checkpoint40, checkpoint41
Changes since 1.2: +36 -28 lines
Updates for multi-threaded AIM with support for both latlon
and CS.
Needs compatible changes to verfication/

1 cnh 1.3 C $Header: /u/gcmpack/models/MITgcmUV/pkg/aim/phy_convmf.F,v 1.2 2001/02/02 21:36:29 adcroft Exp $
2     C $Name: $
3 adcroft 1.2
4     cmolt SUBROUTINE CONVMF (PSA,SE,QA,QSAT,
5     SUBROUTINE CONVMF (PSA,TA,QA,QSAT,
6 cnh 1.3 * IDEPTH,CBMF,PRECNV,DFSE,DFQA,
7     I myThid)
8 adcroft 1.2 C--
9     C-- SUBROUTINE CONVMF (PSA,SE,QA,QSAT,
10     C-- * IDEPTH,CBMF,PRECNV,DFSE,DFQA)
11     C--
12     C-- Purpose: Compute convective fluxes of dry static energy and moisture
13     C-- using a simplified mass-flux scheme
14     C-- Input: PSA = norm. surface pressure [p/p0] (2-dim)
15     C-- SE = dry static energy (3-dim)
16     C-- QA = specific humidity [g/kg] (3-dim)
17     C-- QSAT = saturation spec. hum. [g/kg] (3-dim)
18     C-- Output: IDEPTH = convection depth in layers (2-dim)
19     C-- CBMF = cloud-base mass flux (2-dim)
20     C-- PRECNV = convective precipitation [g/(m^2 s)] (2-dim)
21     C-- DFSE = net flux of d.s.en. into each atm. layer (3-dim)
22     C-- DFQA = net flux of sp.hum. into each atm. layer (3-dim)
23     C--
24    
25     IMPLICIT rEAL*8 ( A-H,O-Z)
26 cnh 1.3 INTEGER myThid
27 adcroft 1.2
28     C Resolution parameters
29     C
30 cnh 1.3 #include "EEPARAMS.h"
31    
32 adcroft 1.2 #include "atparam.h"
33     #include "atparam1.h"
34     #include "Lev_def.h"
35     C
36 cnh 1.3 INTEGER NLON, NLAT, NLEV, NGP
37 adcroft 1.2 PARAMETER ( NLON=IX, NLAT=IL, NLEV=KX, NGP=NLON*NLAT )
38     C
39     C Physical constants + functions of sigma and latitude
40     C
41     #include "com_physcon.h"
42     C
43     C Convection constants
44     C
45     #include "com_cnvcon.h"
46     C
47     REAL PSA(NGP), SE(NGP,NLEV), QA(NGP,NLEV), QSAT(NGP,NLEV)
48     C
49     INTEGER IDEPTH(NGP)
50     REAL CBMF(NGP), PRECNV(NGP), DFSE(NGP,NLEV), DFQA(NGP,NLEV)
51     C
52     INTEGER ITOP(NGP)
53     REAL SM(NGP,NLEV), ENTR(NGP,2:NLEV-1)
54     REAL FM0(NGP), DENTR(NGP)
55     C
56     REAL Th(NGP,NLEV), Ta(NGP,NLEV)
57     REAL dThdp(NGP,NLEV), dThdpHat(NGP,NLEV)
58     REAL stab(NGP,NLEV)
59     REAL Prefw(NLEV), Prefs(NLEV)
60     DATA Prefs / 75., 250., 500., 775., 950./
61     DATA Prefw / 0., 150., 350., 650., 900./
62     REAL Pground
63     DATA pground /1000./
64     REAL FDMUS
65 cnh 1.3
66     INTEGER J, K, K1
67 adcroft 1.2 C
68     C 1. Initialization of output and workspace arrays
69     C
70     DO J=1,NGP
71     FM0(J)=0.
72 cnh 1.3 IF ( NLEVxy(J,myThid) .NE. 0 ) THEN
73     FM0(J)=P0*DSIG(NLEVxy(J,myThid))/(GG*TRCNV*3600)
74 adcroft 1.2 ENDIF
75     DENTR(J)=ENTMAX/(SIG(NLEV-1)-0.5)
76     ENDDO
77     C
78     DO K=1,NLEV
79     DO J=1,NGP
80     DFSE(J,K)=0.0
81     DFQA(J,K)=0.0
82     ENDDO
83     ENDDO
84     C
85     C
86     DO J=1,NGP
87 cnh 1.3 ITOP(J) =NLEVxy(J,myThid)
88 adcroft 1.2 CBMF(J) =0.0
89     PRECNV(J)=0.0
90     ENDDO
91     C
92     C Saturation moist static energy
93     cmolt DO J=1,NGP
94 cnh 1.3 cmolt DO K=1,NLEVxy(J,myThid)
95 adcroft 1.2 cmolt SM(J,K)=SE(J,K)+ALHC*QSAT(J,K)
96     cmolt ENDDO
97     cmolt ENDDO
98     C
99     C Entrainment profile (up to sigma = 0.5)
100     DO J=1,NGP
101 cnh 1.3 DO K=2,NLEVxy(J,myThid)-1
102 adcroft 1.2 ENTR(J,K)=MAX(0.,SIG(K)-0.5)*DENTR(J)
103     ENDDO
104     ENDDO
105     C
106     C-- 2. Check of conditions for convection
107     C
108     C 2.1 Conditional instability
109     C
110     cmolt DO J=1,NGP
111 cnh 1.3 cmolt DO K=NLEVxy(J,myThid)-2,2,-1
112 adcroft 1.2 cmolt SMB=SM(J,K)+WVI(K,2)*(SM(J,K+1)-SM(J,K))
113 cnh 1.3 cmolt IF (SM(J,NLEVxy(J,myThid)).GT.SMB) ITOP(J)=K
114 adcroft 1.2 cmolt ENDDO
115     cmolt ENDDO
116     C
117     C New writing of the Conditional stability
118     C ----------------------------------------
119     DO J=1,NGP
120 cnh 1.3 DO k=1,NLEVxy(J,myThid)
121 adcroft 1.2 Th(J,K)=Ta(J,K)*(Pground/Prefs(k))**(RD/CP)
122     ENDDO
123     ENDDO
124     C
125     DO J=1,NGP
126     dThdp(J,1)=0.
127 cnh 1.3 IF ( NLEVxy(J,myThid) .NE. 0 ) THEN
128     dThdp(J,NLEVxy(J,myThid))=0.
129 adcroft 1.2 ENDIF
130 cnh 1.3 DO k=2,NLEVxy(J,myThid)
131 adcroft 1.2 dThdp(J,K-1)=(Th(J,K-1)-Th(J,K))
132     & *((Prefw(k)/Pground)**(RD/CP))*CP
133     ENDDO
134     ENDDO
135     C
136     DO J=1,NGP
137 cnh 1.3 IF ( NLEVxy(J,myThid) .NE. 0 ) THEN
138     dThdpHat(J,NLEVxy(J,myThid))=dThdp(J,NLEVxy(J,myThid))
139 adcroft 1.2 ENDIF
140     ENDDO
141     C
142     DO J=1,NGP
143 cnh 1.3 DO k=NLEVxy(J,myThid)-1,2,-1
144 adcroft 1.2 dThdpHat(J,K)=dThdpHat(J,K+1)+dThdp(J,k)
145     ENDDO
146     ENDDO
147     C
148     DO J=1,NGP
149 cnh 1.3 DO k=2,NLEVxy(J,myThid)-1
150     stab(J,K)=dThdpHat(J,K)+ALHC*(QSAT(J,K)-QSAT(J,NLEVxy(J,myThid)))
151 adcroft 1.2 & -WVI(K,2)*(dThdp(J,K) +ALHC*(QSAT(J,K) -QSAT(J,K+1)) )
152     ENDDO
153     ENDDO
154     C
155     DO J=1,NGP
156 cnh 1.3 DO K=NLEVxy(J,myThid)-2,2,-1
157 adcroft 1.2 if(stab(J,K).lt.0.) ITOP(J)=K
158     ENDDO
159     ENDDO
160     C
161     C 2.2 Humidity exceeding prescribed threshold
162     C
163     DO J=1,NGP
164 cnh 1.3 IF ( NLEVxy(J,myThid) .NE. 0 ) THEN
165     IF (QA(J,NLEVxy(J,myThid)).LT.RHBL*QSAT(J,NLEVxy(J,myThid)))
166     & ITOP(J)=NLEVxy(J,myThid)
167 adcroft 1.2 ENDIF
168 cnh 1.3 IDEPTH(J)=NLEVxy(J,myThid)-ITOP(J)
169 adcroft 1.2 ENDDO
170     C
171     C-- 3. Convection over selected grid-points
172     C
173     DO 300 J=1,NGP
174 cnh 1.3 IF (ITOP(J).EQ.NLEVxy(J,myThid)) GO TO 300
175 adcroft 1.2 C
176     C 3.1 Boundary layer (cloud base)
177     C
178 cnh 1.3 K =NLEVxy(J,myThid)
179 adcroft 1.2 K1=K-1
180     C
181     C Dry static energy and moisture at upper boundary
182     cch SB=SE(J,K1)+WVI(K1,2)*(SE(J,K)-SE(J,K1))
183     QB=QA(J,K1)+WVI(K1,2)*(QA(J,K)-QA(J,K1))
184     cch QB=QA(J,K1)
185     C
186     C Cloud-base mass flux
187     DQSAT=MAX(QSAT(J,K)-QB,0.05*QSAT(J,K))
188     FMASS=FM0(J)*PSA(J)*(QA(J,K)-RHBL*QSAT(J,K))/DQSAT
189     CBMF(J)=FMASS
190     C
191     C Upward fluxes at upper boundary
192     cch FUS=FMASS*SE(J,K)
193 cnh 1.3 C_jmc FUQ=FMASS*QSAT(J,K)
194     FUQ=FMASS*MAX( QSAT(J,K), MIN(QB,QA(J,K)) )
195 adcroft 1.2 C
196     C Downward fluxes at upper boundary
197     cch FDS=FMASS*SB
198     FDQ=FMASS*QB
199     C
200     C Net flux of dry static energy and moisture
201     cch DFSE(J,K)=FDS-FUS
202     DFSE(J,K)=FMASS*dThdp(J,K1)*(1-WVI(K1,2))
203     FDMUS=FMASS*dThdp(J,K1)*(1-WVI(K1,2))
204     DFQA(J,K)=FDQ-FUQ
205     C
206     C 3.2 Intermediate layers (entrainment)
207     C
208 cnh 1.3 DO K=NLEVxy(J,myThid)-1,ITOP(J)+1,-1
209 adcroft 1.2 K1=K-1
210     C
211     C Fluxes at lower boundary
212     cch DFSE(J,K)=FUS-FDS
213     DFQA(J,K)=FUQ-FDQ
214     C
215     C Mass entrainment
216     ENMASS=ENTR(J,K)*PSA(J)*FMASS
217     FMASS=FMASS+ENMASS
218     C
219     C Upward fluxes at upper boundary
220     cch FUS=FUS+ENMASS*SE(J,K)
221     FUQ=FUQ+ENMASS*QA(J,K)
222     C
223     C Downward fluxes at upper boundary
224     cch SB=SE(J,K1)+WVI(K1,2)*(SE(J,K)-SE(J,K1))
225     QB=QA(J,K1)+WVI(K1,2)*(QA(J,K)-QA(J,K1))
226     cch QB=QA(J,K1)
227     cch FDS=FMASS*SB
228     FDQ=FMASS*QB
229     C
230     C Net flux of dry static energy and moisture
231     cch DFSE(J,K)=DFSE(J,K)+FDS-FUS
232     DFSE(J,K)=FMASS*(1-WVI(K1,2))*dThdp(J,K1)+
233     & (FMASS-ENMASS)*WVI(K,2)*dThdp(J,K)
234     FDMUS=FDMUS+ FMASS*(1-WVI(K1,2))*dThdp(J,K1)+
235     & (FMASS-ENMASS)*WVI(K,2)*dThdp(J,K)
236     DFQA(J,K)=DFQA(J,K)+FDQ-FUQ
237     C
238     ENDDO
239     c
240     C 3.3 Top layer (condensation and detrainment)
241     C
242     K=ITOP(J)
243     C
244     C Flux of convective precipitation
245     QSATB=QSAT(J,K)+WVI(K,2)*(QSAT(J,K+1)-QSAT(J,K))
246     PRECNV(J)=MAX(FUQ-FMASS*QSATB,0.0)
247     C
248     C Net flux of dry static energy and moisture
249     cch DFSE(J,K)=FUS-FDS+ALHC*PRECNV(J)
250     DFSE(J,K)=-FDMUS+ALHC*PRECNV(J)
251     DFQA(J,K)=FUQ-FDQ-PRECNV(J)
252     C
253     300 CONTINUE
254     C
255     RETURN
256     END

  ViewVC Help
Powered by ViewVC 1.1.22