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

Annotation of /MITgcm/pkg/aim/phy_vdifsc.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
Changes since 1.2: +28 -26 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_vdifsc.F,v 1.2 2001/02/02 21:36:29 adcroft Exp $
2     C $Name: $
3 adcroft 1.2
4     cch SUBROUTINE VDIFSC (UA,VA,SE,RH,QA,QSAT,
5     SUBROUTINE VDIFSC (UA,VA,Ta,RH,QA,QSAT,
6 cnh 1.3 & UTENVD,VTENVD,TTENVD,QTENVD,
7     & myThid)
8 adcroft 1.2 C-
9     C-- SUBROUTINE VDIFSC (UA,VA,SE,RH,QA,QSAT,
10     C-- & UTENVD,VTENVD,TTENVD,QTENVD)
11     C-
12     C-- Purpose: Compute tendencies of momentum, energy and moisture
13     C-- due to vertical diffusion and shallow convection
14     C-- Input: UA = u-wind (3-dim)
15     C-- VA = v-wind (3-dim)
16     C-- SE = dry static energy (3-dim)
17     C-- RH = relative humidity [0-1] (3-dim)
18     C-- QA = specific humidity [g/kg] (3-dim)
19     C-- QSAT = saturation sp. humidity [g/kg] (3-dim)
20     C-- Output: UTENVD = u-wind tendency (3-dim)
21     C-- VTENVD = v-wind tendency (3-dim)
22     C-- TTENVD = temperature tendency (3-dim)
23     C-- QTENVD = sp. humidity tendency [g/(kg s)] (3-dim)
24     C-
25    
26    
27     IMPLICIT rEAL*8 (A-H,O-Z)
28 cnh 1.3 INTEGER myThid
29 adcroft 1.2
30     C Resolution parameters
31    
32     #include "atparam.h"
33     #include "atparam1.h"
34 cnh 1.3 #include "EEPARAMS.h"
35 adcroft 1.2 #include "Lev_def.h"
36     C
37     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 Vertical diffusion constants
44     C
45     #include "com_vdicon.h"
46     C
47     REAL UA(NGP,NLEV), VA(NGP,NLEV), SE(NGP,NLEV),
48     & RH(NGP,NLEV), QA(NGP,NLEV), QSAT(NGP,NLEV)
49     C
50     REAL UTENVD(NGP,NLEV), VTENVD(NGP,NLEV),
51     & TTENVD(NGP,NLEV), QTENVD(NGP,NLEV)
52     C
53     INTEGER NL1(NGP)
54     REAL RTST(NGP)
55     REAL RNL1(NGP)
56     C
57     REAL Th(NGP,NLEV), Ta(NGP,NLEV)
58     REAL dThdp
59     REAL stab(NGP)
60     REAL AUX(NGP)
61     REAL Prefw(NLEV), Prefs(NLEV)
62     DATA Prefs / 75., 250., 500., 775., 950./
63     DATA Prefw / 0., 150., 350., 650., 900./
64     REAL Pground
65     DATA pground /1000./
66     Cchdbg
67     REAL xindconv1
68     SAVE xindconv1
69     REAL xindconv
70     SAVE xindconv
71     INTEGER npas
72     SAVE npas
73     LOGICAL ifirst
74     DATA ifirst /.TRUE./
75     SAVE ifirst
76     C
77     C-- 1. Initalization
78     C
79     DO K=1,NLEV
80     DO J=1,NGP
81     UTENVD(J,K) = 0.
82     VTENVD(J,K) = 0.
83     TTENVD(J,K) = 0.
84     QTENVD(J,K) = 0.
85     ENDDO
86     ENDDO
87     c
88     C
89     C *****************************************
90     C *****************************************
91     Cchdbg
92     if(ifirst) then
93     xindconv=0.
94     xindconv1=0.
95     npas=0
96     ifirst=.FALSE.
97     endif
98     npas = npas +1
99     Cchdbg
100     C ******************************************
101     C *****************************************
102     C
103     C-- 2. Vertical diffusion and shallow convection
104     C
105     DO J=1,NGP
106 cnh 1.3 NL1(J)=NLEVxy(J,myThid)-1
107 adcroft 1.2 ENDDO
108     C
109     RTVD = -1./(3600.*TRVDI)
110     RTSQ = -1./(3600.*TRSHC)
111     C
112     DO J=1,NGP
113 cnh 1.3 IF ( NLEVxy(J,myThid) .GT. 0 ) THEN
114     RTST(J) = RTSQ*DSIG(NL1(J))/((DSIG(NLEVxy(J,myThid))+DSIG(NL1(J)))*CP)
115     RNL1(J) = -DSIG(NLEVxy(J,myThid))/DSIG(NL1(J))
116 adcroft 1.2 ENDIF
117     ENDDO
118     C
119     C
120     C New writing of the Conditional stability
121     C ----------------------------------------
122     DO J=1,NGP
123 cnh 1.3 IF ( NLEVxy(J,myThid) .GT. 0 ) THEN
124     DO k=NL1(J),NLEVxy(J,myThid)
125 adcroft 1.2 Th(J,K)=Ta(J,K)*(Pground/Prefs(k))**(RD/CP)
126     ENDDO
127     ENDIF
128     ENDDO
129     C
130     DO J=1,NGP
131 cnh 1.3 IF ( NLEVxy(J,myThid) .GT. 0 ) THEN
132     dThdp=(Th(J,NL1(J))-Th(J,NLEVxy(J,myThid)))
133     & *((Prefw(NLEVxy(J,myThid))/Pground)**(RD/CP))*CP
134     stab(J)=dThdp+ALHC*(QSAT(J,NL1(J))-QSAT(J,NLEVxy(J,myThid)))
135 adcroft 1.2 ENDIF
136     ENDDO
137     121 continue
138     C
139     DO J=1,NGP
140     C
141 cnh 1.3 cch DMSE = (SE(J,NLEVxy(J,myThid))-SE(J,NL1(J)))+
142     cch & ALHC*(QA(J,NLEVxy(J,myThid))-QSAT(J,NL1(J)))
143 adcroft 1.2 DMSE = - stab(J)
144 cnh 1.3 IF ( NLEVxy(J,myThid) .GT. 0 ) THEN
145     QEQL = MIN(QA(J,NLEVxy(J,myThid)),RH(J,NL1(J))*QSAT(J,NLEVxy(J,myThid)))
146     cchdbg QEQL = MIN(QA(J,NLEVxy(J,myThid)),QA(J,NL1(J)))
147 adcroft 1.2 ENDIF
148     C
149     IF (DMSE.GE.0.0) THEN
150     C
151     C ***************************************************
152     C ***************************************************
153     C chdbg
154     if(J.ge.6336 .and. J.eq.6348) then
155     xindconv=xindconv+1./13.
156     endif
157     if(J.ge.4160 .and. J.eq.4172) then
158     xindconv1=xindconv1+1./13.
159     endif
160     if(npas.eq.960 .and. J.eq.1) then
161     write(0,*) 'xindconv=',xindconv
162     write(0,*) 'xindconv1=',xindconv1
163     endif
164     Cchdbg
165     C ****************************************************
166     C ****************************************************
167     C
168     C 2.1 Shallow convection
169     C
170 cnh 1.3 IF ( NLEVxy(J,myThid) .GT. 0 ) THEN
171     TTENVD(J,NLEVxy(J,myThid)) = RTST(J)*DMSE
172     TTENVD(J,NL1(J)) = RNL1(J)*TTENVD(J,NLEVxy(J,myThid))
173     QTENVD(J,NLEVxy(J,myThid)) = RTSQ*(QA(J,NLEVxy(J,myThid))-QEQL)
174     QTENVD(J,NL1(J)) = RNL1(J)*QTENVD(J,NLEVxy(J,myThid))
175 adcroft 1.2 ENDIF
176     C
177     ELSE
178     C
179     C 2.2 Vertical diffusion of moisture
180    
181 cnh 1.3 QTENVD(J,NLEVxy(J,myThid)) = RTVD*(QA(J,NLEVxy(J,myThid))-QEQL)
182     QTENVD(J,NL1(J)) = RNL1(J)*QTENVD(J,NLEVxy(J,myThid))
183 adcroft 1.2 C
184     ENDIF
185     C
186     ENDDO
187     C
188     RETURN
189     END

  ViewVC Help
Powered by ViewVC 1.1.22