/[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.5 - (hide annotations) (download)
Fri Sep 27 20:05:11 2002 UTC (21 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint46n_post, checkpoint48f_post, checkpoint51k_post, checkpoint53f_post, checkpoint47j_post, checkpoint54a_pre, checkpoint55c_post, checkpoint53b_pre, checkpoint48d_pre, checkpoint51l_post, checkpoint51j_post, branch-exfmods-tag, checkpoint47e_post, checkpoint57m_post, checkpoint52l_pre, checkpoint48i_post, checkpoint52e_pre, hrcube4, hrcube5, checkpoint57g_pre, checkpoint52j_post, checkpoint47f_post, checkpoint48d_post, checkpoint51o_pre, checkpoint57f_post, checkpoint46j_post, checkpoint47c_post, checkpoint50e_post, checkpoint52e_post, checkpoint50c_post, checkpoint46i_post, checkpoint51n_pre, checkpoint47d_post, checkpoint57j_post, checkpoint47a_post, checkpoint57b_post, checkpoint52d_pre, checkpoint53c_post, checkpoint53d_post, checkpoint57f_pre, checkpoint48a_post, checkpoint55d_pre, checkpoint51f_pre, checkpoint57g_post, checkpoint48e_post, checkpoint57c_pre, checkpoint48h_post, checkpoint55j_post, checkpoint56b_post, checkpoint50c_pre, checkpoint57h_pre, branchpoint-genmake2, checkpoint46k_post, checkpoint52j_pre, checkpoint54a_post, branch-netcdf, checkpoint50d_pre, checkpoint55h_post, checkpoint51r_post, checkpoint47i_post, checkpoint52b_pre, checkpoint52n_post, checkpoint54b_post, checkpoint46l_pre, checkpoint46j_pre, checkpoint51i_post, checkpoint57e_post, checkpoint54d_post, checkpoint47h_post, checkpoint48c_post, checkpoint46l_post, checkpoint56c_post, checkpoint54e_post, checkpoint55b_post, checkpoint51e_post, checkpoint51b_post, checkpoint51l_pre, checkpoint52m_post, checkpoint51c_post, checkpoint55, checkpoint53a_post, checkpoint55a_post, checkpoint57a_post, checkpoint48, checkpoint49, checkpoint47b_post, checkpoint56, checkpoint57o_post, checkpoint55g_post, checkpoint57h_done, checkpoint51o_post, checkpoint48g_post, checkpoint57k_post, checkpoint57d_post, checkpoint55f_post, checkpoint57i_post, checkpoint51q_post, checkpoint52l_post, checkpoint52k_post, checkpoint57h_post, checkpoint57a_pre, checkpoint54, checkpoint57, checkpoint53b_post, checkpoint51, checkpoint50, checkpoint53, checkpoint52, checkpoint50d_post, checkpoint52d_post, checkpoint51b_pre, checkpoint52a_post, checkpoint47g_post, checkpoint52b_post, checkpoint53g_post, checkpoint52f_post, checkpoint57n_post, checkpoint52c_post, checkpoint46m_post, checkpoint57p_post, checkpoint51h_pre, checkpoint50g_post, checkpoint50b_pre, checkpoint51g_post, ecco_c52_e35, checkpoint54f_post, checkpoint51f_post, checkpoint48b_post, checkpoint50b_post, eckpoint57e_pre, checkpoint57c_post, checkpoint50f_post, checkpoint50a_post, checkpoint50f_pre, checkpoint52a_pre, checkpoint47d_pre, checkpoint51d_post, checkpoint48c_pre, checkpoint51m_post, checkpoint51t_post, checkpoint53d_pre, checkpoint47, checkpoint55e_post, checkpoint54c_post, checkpoint50h_post, checkpoint52i_post, checkpoint51a_post, checkpoint50e_pre, checkpoint50i_post, checkpoint51p_post, checkpoint51n_post, checkpoint55i_post, checkpoint51i_pre, checkpoint57l_post, checkpoint52i_pre, checkpoint51u_post, checkpoint52h_pre, checkpoint52f_pre, hrcube_1, hrcube_2, hrcube_3, checkpoint56a_post, checkpoint51s_post, checkpoint55d_post
Branch point for: netcdf-sm0, branch-genmake2, branch-nonh, tg2-branch, checkpoint51n_branch, branch-exfmods-curt
Changes since 1.4: +41 -31 lines
Clean up AIM package (and keep the results unchanged):
a) include CPP_OPTION and use IMPLICT NONE in all routines ;
  declare all the variables _RL ;
b) use _d 0 for all numerical constants in Physics package,
  so that the code works with g77 (and give the right answer)
c) use ifdef ALLOW_AIM everywhere so that the package can be
 compiled without increasing the memory size.
d) clean-up the AIM interface (remove commented lines, unused
  variables ...)

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

  ViewVC Help
Powered by ViewVC 1.1.22