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

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

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


Revision 1.14 - (hide annotations) (download)
Mon Aug 1 19:34:57 2005 UTC (18 years, 9 months ago) by cnh
Branch: MAIN
CVS Tags: HEAD
Changes since 1.13: +1 -1 lines
FILE REMOVED
Emptying aim/ since aim_v23 is now "the one" for all experiements.

1 cnh 1.14 C $Header: /u/gcmpack/MITgcm/pkg/aim/aim_do_atmos_physics.F,v 1.13 2003/09/29 19:24:31 edhill Exp $
2 jmc 1.3 C $Name: $
3 adcroft 1.2
4     #include "AIM_OPTIONS.h"
5    
6 jmc 1.12 SUBROUTINE AIM_DO_PHYSICS( bi, bj, currentTime, myIter, myThid )
7 jmc 1.11
8 adcroft 1.2 C /==================================================================\
9     C | S/R AIM_DO_ATMOS_PHYSICS |
10     C |==================================================================|
11     C | Interface interface between atmospheric physics package and the |
12     C | dynamical model. |
13     C | Routine calls physics pacakge after mapping model variables to |
14     C | the package grid. Package should derive and set tendency terms |
15     C | which can be included as external forcing terms in the dynamical |
16     C | tendency routines. Packages should communicate this information |
17     C | through common blocks. |
18     C \==================================================================/
19 jmc 1.10 IMPLICIT NONE
20 adcroft 1.2
21     C -------------- Global variables ------------------------------------
22 jmc 1.10 C-- size for MITgcm & Physics package :
23     #include "AIM_SIZE.h"
24 cnh 1.4
25 jmc 1.10 C-- MITgcm
26 adcroft 1.2 #include "EEPARAMS.h"
27     #include "PARAMS.h"
28     #include "DYNVARS.h"
29     #include "GRID.h"
30 cnh 1.4 #include "SURFACE.h"
31 jmc 1.10
32     C-- Physics package
33 cnh 1.4 #include "AIM_FFIELDS.h"
34 jmc 1.10 #include "AIM_GRID.h"
35 cnh 1.4 #include "com_physvar.h"
36     #include "com_forcing1.h"
37 adcroft 1.2
38     C -------------- Routine arguments -----------------------------------
39 jmc 1.11 c _RL phi_hyd(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
40 adcroft 1.2 _RL currentTime
41 jmc 1.12 INTEGER myIter, myThid
42 cnh 1.4 INTEGER bi, bj
43 adcroft 1.2
44     #ifdef ALLOW_AIM
45     C -------------- Local variables -------------------------------------
46 jmc 1.10 C I,J,K,I2 - Loop counters
47 adcroft 1.2 C tYear - Fraction into year
48     C hInital - Initial height of pressure surfaces (m)
49     C pSurfs - Pressure surfaces (Pa)
50     C Katm - Atmospheric K index
51     INTEGER I
52     INTEGER I2
53     INTEGER J
54     INTEGER K
55 jmc 1.10 _RL tYear
56     _RL hInitial(Nr)
57     _RL hInitialW(Nr)
58 jmc 1.8 DATA hInitial / 17338.0,10090.02,5296.88,2038.54,418.038/
59 adcroft 1.2 SAVE hInitial
60 jmc 1.8 DATA hInitialW / 15090.4, 8050.96, 4087.75, 1657.54, 0. /
61 jmc 1.10 _RL pSurfs(Nr)
62 jmc 1.8 DATA pSurfs / 75.D2, 250.D2, 500.D2, 775.D2, 950.D2 /
63 adcroft 1.2 SAVE pSurfs
64 jmc 1.10 _RL pSurfw(Nr)
65 jmc 1.8 DATA pSurfw / 150.D2, 350.D2, 650.D2, 900.D2, 1000.D2 /
66 adcroft 1.2 SAVE pSurfw
67 jmc 1.10 _RL RD
68     _RL CPAIR
69     _RL pGround
70     _RL RhoG1(sNx*sNy,Nr)
71     c _RL phiTotal(sNx,sNy,Nr)
72     c _RL phiTCount
73     c _RL phiTSum
74     c _RL ans
75     c _RL pvoltotNiv5
76     c SAVE pvoltotNiv5
77     c _RL ptotalNiv5
78 adcroft 1.2 INTEGER Katm
79 cnh 1.4
80 adcroft 1.2 pGround = 1.D5
81     CPAIR = 1004
82     RD = 287
83    
84 cnh 1.4 CALL AIM_DYN2AIM( bi, bj, currentTime, myThid )
85    
86 adcroft 1.2 C Physics package works with sub-domains 1:sNx,1:sNy,1:Nr.
87     C Internal index mapping is linear in X and Y with a second
88     C dimension for the vertical.
89    
90     C Adjustment for heave due to mean heating/cooling
91 edhill 1.13 C ( I do not think the old formula was strictly "correct" for orography
92 adcroft 1.2 C but I have implemented it as was for now. As implemented
93     C the mean heave of the bottom (K=Nr) level is calculated rather than
94     C the mean heave of the base of the atmosphere. )
95 jmc 1.10 c phiTCount = 0.
96     c phiTSum = 0.
97     c DO K=1,Nr
98     c DO J=1,sNy
99     c DO I=1,sNx
100     c phiTotal(I,J,K) = etaN(i,j,bi,bj)
101     c phiTCount = phiTCount + hFacC(i,j,Nr,bi,bj)
102     c ENDDO
103     c ENDDO
104     c ENDDO
105     c DO K=1,Nr
106     c DO J=1,sNy
107     c DO I=1,sNx
108     c phiTotal(I,J,K) = phiTotal(I,J,K) +
109     c & recip_rhoConst*(phi_hyd(i,j,k))
110     c ENDDO
111     c ENDDO
112     c ENDDO
113     c DO J=1,sNy
114     c DO I=1,sNx
115     c phiTSum = phiTSum + phiTotal(I,J,Nr)
116     c ENDDO
117     c ENDDO
118     c ans = phiTCount
119 adcroft 1.2 C _GLOBAL_SUM_R8( phiTCount, myThid )
120 jmc 1.10 c phiTcount = ans
121     c ans = phiTSum
122 adcroft 1.2 C _GLOBAL_SUM_R8( phiTSum, myThid )
123 jmc 1.10 c phiTSum = ans
124 adcroft 1.2 C ptotalniv5=phiTSum/phiTCount
125 jmc 1.10 c ptotalniv5=0.
126 adcroft 1.2
127 jmc 1.8 #ifndef OLD_AIM_INTERFACE
128 jmc 1.10 C_jmc: Because AIM physics LSC is not applied in the stratosphere (top level),
129     C ==> move water wapor from the stratos to the surface level.
130 cnh 1.4 DO J = 1-Oly, sNy+Oly
131     DO I = 1-Olx, sNx+Olx
132 jmc 1.9 k = ksurfC(i,j,bi,bj)
133     IF (k.LE.Nr)
134     & salt(I,J,k,bi,bj) = salt(I,J,k,bi,bj)
135     & + salt(I,J,Nr,bi,bj)*drF(Nr)*recip_drF(k)
136 cnh 1.4 salt(I,J,Nr,bi,bj) = 0.
137     ENDDO
138     ENDDO
139 jmc 1.8 #endif /* OLD_AIM_INTERFACE */
140 cnh 1.4
141     C Note the mapping here is only valid for one tile per proc.
142 adcroft 1.2 DO K = 1, Nr
143     DO J = 1, sNy
144     DO I = 1, sNx
145     I2 = (sNx)*(J-1)+I
146     Katm = _KD2KA( K )
147 jmc 1.8 C - to reproduce old results (coupled run, summer 2000) :
148     UG1(I2,Katm,myThid) = uVel(I,J,K,bi,bj)
149     VG1(I2,Katm,myThid) = vVel(I,J,K,bi,bj)
150 cnh 1.4 C Physics works with temperature - not potential temp.
151     TG1(I2,Katm,myThid) = theta(I,J,K,bi,bj)
152 jmc 1.8 & / ((pGround/pSurfs(Katm))**(RD/CPAIR))
153     #ifdef OLD_AIM_INTERFACE
154     QG1(I2,Katm,myThid) = salt(I,J,K,bi,bj)
155     #else
156 cnh 1.4 QG1(I2,Katm,myThid) = MAX(salt(I,J,K,bi,bj), 0. _d 0)
157 jmc 1.8 #endif
158 jmc 1.10 PHIG1(I2,Katm,myThid) = gravity*Hinitial(Katm)
159     c & +(phiTotal(I,J,K)- ptotalniv5 )
160 jmc 1.6 IF (maskC(i,j,k,bi,bj).EQ.1.) THEN
161 jmc 1.8 RHOG1(I2,Katm) = pSurfs(Katm)/RD/TG1(I2,Katm,myThid)
162 jmc 1.6 ELSE
163 adcroft 1.2 RHOG1(I2,Katm)=0.
164 jmc 1.6 ENDIF
165 adcroft 1.2 ENDDO
166     ENDDO
167     ENDDO
168    
169 cnh 1.4 c---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
170 jmc 1.10 C_jmc: add square of surface wind speed (center of C grid) = 2 * KE_surf
171 cnh 1.4 DO J = 1, sNy
172     DO I = 1, sNx
173 jmc 1.7 I2 = I+(J-1)*sNx
174 jmc 1.8 #ifdef OLD_AIM_INTERFACE
175     C - to reproduce old results (coupled run, summer 2000) :
176     Vsurfsq(I2,myThid) = 0.
177     IF (NLEVxyU(I2,myThid).GT.0)
178     & Vsurfsq(I2,myThid) = Vsurfsq(I2,myThid)
179     & +UG1(I2,NLEVxyU(I2,myThid),myThid)
180     & *UG1(I2,NLEVxyU(I2,myThid),myThid)
181     IF (NLEVxyV(I2,myThid).GT.0)
182     & Vsurfsq(I2,myThid) = Vsurfsq(I2,myThid)
183     & +VG1(I2,NLEVxyV(I2,myThid),myThid)
184     & *VG1(I2,NLEVxyV(I2,myThid),myThid)
185     #else /* OLD_AIM_INTERFACE */
186 jmc 1.7 K = ksurfC(i,j,bi,bj)
187     IF (K.LE.Nr) THEN
188 cnh 1.4 Vsurfsq(I2,myThid) = 0.5 * (
189     & uVel(I,J,K,bi,bj)*uVel(I,J,K,bi,bj)
190     & + uVel(I+1,J,K,bi,bj)*uVel(I+1,J,K,bi,bj)
191     & + vVel(I,J,K,bi,bj)*vVel(I,J,K,bi,bj)
192     & + vVel(I,J+1,K,bi,bj)*vVel(I,J+1,K,bi,bj)
193     & )
194 jmc 1.7 ELSE
195     Vsurfsq(I2,myThid) = 0.
196     ENDIF
197 jmc 1.8 #endif /* OLD_AIM_INTERFACE */
198 cnh 1.4 ENDDO
199     ENDDO
200     c---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
201    
202 adcroft 1.2 C
203     C Set geopotential surfaces
204     C -------------------------
205     DO J=1,sNy
206     DO I=1,sNx
207     I2 = (sNx)*(J-1)+I
208 cnh 1.4 IF ( Nlevxy(I2,myThid) .NE. 0 ) THEN
209     PHI0(I2,myThid) = gravity*Hinitialw(Nlevxy(I2,myThid))
210 adcroft 1.2 ELSE
211 cnh 1.4 PHI0(I2,myThid) = 0.
212 adcroft 1.2 ENDIF
213     ENDDO
214     ENDDO
215 cnh 1.4
216 adcroft 1.2 C
217     C Physics package works with log of surface pressure
218     C Get surface pressure from pbot-dpref/dz*Z'
219     DO J=1,sNy
220     DO I=1,sNx
221     I2 = (sNx)*(J-1)+I
222 cnh 1.4 IF ( Nlevxy(I2,myThid) .NE. 0 ) THEN
223     PNLEVW(I2,myThid) = PsurfW(Nlevxy(I2,myThid))/pGround
224 adcroft 1.2 ELSE
225     C Dummy value for land
226 jmc 1.8 PNLEVW(I2,myThid) = PsurfW(Nr)/pGround
227 adcroft 1.2 ENDIF
228 cnh 1.4 PSLG1(I2,myThid) = 0.
229 adcroft 1.2 ENDDO
230     ENDDO
231     C
232     C
233     C Physics package needs to know time of year as a fraction
234     tYear = currentTime/(86400.*360.) -
235     & FLOAT(INT(currentTime/(86400.*360.)))
236 cnh 1.4
237 adcroft 1.2 C
238     C Load external data needed by physics package
239 jmc 1.9 C 1. Albedo (between 0-1)
240     C 2. Soil moisture (between 0-1)
241     C 3. Surface temperatures (in situ Temp. [K])
242 adcroft 1.2 C 4. Snow depth - assume no snow for now
243     C 5. Sea ice - assume no sea ice for now
244     C 6. Land sea mask - infer from exact zeros in soil moisture dataset
245     C 7. Surface geopotential - to be done when orography is in
246     C dynamical kernel. Assume 0. for now.
247 jmc 1.10
248     C Load in surface albedo data (in [0,1]) from aim_albedo to alb0 :
249 adcroft 1.2 DO J=1,sNy
250     DO I=1,sNx
251     I2 = (sNx)*(J-1)+I
252 cnh 1.4 alb0(I2,myThid) = 0.
253 jmc 1.9 alb0(I2,myThid) = aim_albedo(I,J,bi,bj)
254 adcroft 1.2 ENDDO
255     ENDDO
256 jmc 1.10 C Load in surface temperature data from aim_surfTemp to stl1 & sst1 :
257 adcroft 1.2 DO J=1,sNy
258     DO I=1,sNx
259     I2 = (sNx)*(J-1)+I
260 cnh 1.4 sst1(I2,myThid) = 300.
261     stl1(I2,myThid) = 300.
262 cnh 1.5 sst1(I2,myThid) = aim_surfTemp(I,J,bi,bj)
263     stl1(I2,myThid) = aim_surfTemp(I,J,bi,bj)
264 adcroft 1.2 ENDDO
265     ENDDO
266     C
267 jmc 1.10 C Load in soil moisture data (in [0,1]) from aim_soilMoisture to soilq1 :
268 adcroft 1.2 C??? NOT CLEAR scale for bucket depth of 75mm which is what Franco uses.
269     DO J=1,sNy
270     DO I=1,sNx
271     I2 = (sNx)*(J-1)+I
272 cnh 1.4 soilq1(I2,myThid) = 0.
273 jmc 1.9 soilq1(I2,myThid) = aim_soilMoisture(I,J,bi,bj)
274 adcroft 1.2 ENDDO
275     ENDDO
276     C Set snow depth, sea ice to zero for now
277 cnh 1.4 C Land-sea mask ( figure this out from where
278     C soil moisture is exactly zero ).
279 adcroft 1.2 DO J=1,sNy
280     DO I=1,sNx
281     I2 = (sNx)*(J-1)+I
282 cnh 1.4 fMask1(I2,myThid) = 1.
283     IF ( soilq1(I2,myThid) .EQ. 0. ) fMask1(I2,myThid) = 0.
284     oice1(I2,myThid) = 0.
285     snow1(I2,myThid) = 0.
286 adcroft 1.2 ENDDO
287     ENDDO
288     C open(77,file='lsmask',form='unformatted')
289     C write(77) fmask1
290     C close(77)
291 jmc 1.10
292 adcroft 1.2 C Addition may 15 . Reset humidity to 0. if negative
293     C ---------------------------------------------------
294 jmc 1.8 #ifdef OLD_AIM_INTERFACE
295     DO K=1,Nr
296     DO J=1-OLy,sNy+OLy
297     DO I=1-Olx,sNx+OLx
298     IF ( salt(i,j,k,bi,bj) .LT. 0. .OR. K .EQ. Nr ) THEN
299     salt(i,j,k,bi,bj) = 0.
300     ENDIF
301     ENDDO
302     ENDDO
303     ENDDO
304     #endif /* OLD_AIM_INTERFACE */
305 cnh 1.4
306     CALL PDRIVER( tYear, myThid )
307 adcroft 1.2
308 jmc 1.3 #ifdef ALLOW_TIMEAVE
309 adcroft 1.2 C Calculate diagnostics for AIM
310     CALL AIM_CALC_DIAGS( bi, bj, currentTime, myThid )
311 jmc 1.3 #endif /* ALLOW_TIMEAVE */
312 cnh 1.4
313     CALL AIM_AIM2DYN( bi, bj, currentTime, myThid )
314 jmc 1.10
315 adcroft 1.2 #endif /* ALLOW_AIM */
316    
317     RETURN
318     END

  ViewVC Help
Powered by ViewVC 1.1.22