/[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.3 - (hide annotations) (download)
Tue Mar 6 17:53:02 2001 UTC (23 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: pre38tag1, c37_adj, pre38-close, checkpoint37, checkpoint39, checkpoint38
Branch point for: pre38
Changes since 1.2: +5 -6 lines
use state variable "eta" (replace cg2d_x) ; ALLOW_TIMEAVE (new package)

1 jmc 1.3 C $Header: /u/gcmpack/models/MITgcmUV/pkg/aim/aim_do_atmos_physics.F,v 1.2 2001/02/02 21:36:29 adcroft Exp $
2     C $Name: $
3 adcroft 1.2
4     #include "AIM_OPTIONS.h"
5    
6     SUBROUTINE AIM_DO_ATMOS_PHYSICS( phi_hyd, currentTime, myThid )
7     C /==================================================================\
8     C | S/R AIM_DO_ATMOS_PHYSICS |
9     C |==================================================================|
10     C | Interface interface between atmospheric physics package and the |
11     C | dynamical model. |
12     C | Routine calls physics pacakge after mapping model variables to |
13     C | the package grid. Package should derive and set tendency terms |
14     C | which can be included as external forcing terms in the dynamical |
15     C | tendency routines. Packages should communicate this information |
16     C | through common blocks. |
17     C \==================================================================/
18    
19     C -------------- Global variables ------------------------------------
20     C Physics package
21     #include "atparam.h"
22     #include "atparam1.h"
23     INTEGER NGP
24     INTEGER NLON
25     INTEGER NLAT
26     INTEGER NLEV
27     PARAMETER ( NLON=IX, NLAT=IL, NLEV=KX, NGP=NLON*NLAT )
28     #include "com_physvar.h"
29     #include "com_forcing1.h"
30     #include "Lev_def.h"
31     C MITgcm
32     #include "EEPARAMS.h"
33     #include "PARAMS.h"
34     #include "DYNVARS.h"
35     #include "GRID.h"
36    
37     C -------------- Routine arguments -----------------------------------
38     _RL phi_hyd(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
39     _RL currentTime
40    
41     #ifdef ALLOW_AIM
42     C -------------- Local variables -------------------------------------
43     C I,J,K,I2,J2 - Loop counters
44     C tYear - Fraction into year
45     C mnthIndex - Current month
46     C prevMnthIndex - Month last time this routine was called.
47     C tmp4 - I/O buffer ( 32-bit precision )
48     C fNam - Work space for file names
49     C mnthNam - Month strings
50     C hInital - Initial height of pressure surfaces (m)
51     C pSurfs - Pressure surfaces (Pa)
52     C Katm - Atmospheric K index
53     INTEGER I
54     INTEGER I2
55     INTEGER J
56     INTEGER J2
57     INTEGER K
58     INTEGER IG0
59     INTEGER JG0
60     REAL tYear
61     INTEGER mnthIndex
62     INTEGER prevMnthIndex
63     DATA prevMnthIndex / 0 /
64     SAVE prevMnthIndex
65     LOGICAL FirstCall
66     DATA FirstCall /.TRUE./
67     SAVE FirstCall
68     LOGICAL CALLFirst
69     DATA CALLFirst /.TRUE./
70     SAVE CALLFirst
71     INTEGER nxIo
72     INTEGER nyIo
73     PARAMETER ( nxIo = 128, nyIo = 64 )
74     Real*4 tmp4(nxIo,nyIo)
75     CHARACTER*16 fNam
76     CHARACTER*3 mnthNam(12)
77     DATA mnthNam /
78     & 'jan', 'feb', 'mar', 'apr', 'may', 'jun',
79     & 'jul', 'aug', 'sep', 'oct', 'nov', 'dec' /
80     SAVE mnthNam
81     REAL hInitial(Nr)
82     REAL hInitialW(Nr)
83     DATA hInitial / 418.038,2038.54,5296.88,10090.02,17338.0/
84     SAVE hInitial
85     DATA hInitialW / 0., 1657.54, 4087.75, 8050.96,15090.4 /
86     REAL pSurfs(Nr)
87     DATA pSurfs / 950.D2,775.D2, 500.D2, 250.D2, 75.D2 /
88     SAVE pSurfs
89     REAL pSurfw(Nr)
90     DATA pSurfw /1000.D2, 900.D2, 650.D2, 350.D2, 150.D2 /
91     SAVE pSurfw
92     REAL RD
93     REAL CPAIR
94     REAL RhoG1(sNx*sNy,Nr)
95     INTEGER npasdt
96     DATA npasdt /0/
97     SAVE npasdt
98     REAL Soilqmax
99     REAL phiTotal(sNx,sNy,Nr)
100     _RL phiTCount
101     _RL phiTSum
102     _RL ans
103     real pvoltotNiv5
104     SAVE pvoltotNiv5
105     real ptotalNiv5
106     INTEGER bi, bj
107     INTEGER Katm
108     C
109     pGround = 1.D5
110     CPAIR = 1004
111     RD = 287
112    
113     C Assume only one tile per proc. for now
114     bi = 1
115     bj = 1
116     IG0 = myXGlobalLo
117     JG0 = myYGlobalLo
118    
119     C
120     C Physics package works with sub-domains 1:sNx,1:sNy,1:Nr.
121     C Internal index mapping is linear in X and Y with a second
122     C dimension for the vertical.
123    
124     C Adjustment for heave due to mean heating/cooling
125     C ( I don't think the old formula was strictly "correct" for orography
126     C but I have implemented it as was for now. As implemented
127     C the mean heave of the bottom (K=Nr) level is calculated rather than
128     C the mean heave of the base of the atmosphere. )
129     phiTCount = 0.
130     phiTSum = 0.
131     DO K=1,Nr
132     DO J=1,sNy
133     DO I=1,sNx
134 jmc 1.3 phiTotal(I,J,K) = etaN(i,j,bi,bj)
135 adcroft 1.2 phiTCount = phiTCount + hFacC(i,j,Nr,bi,bj)
136     ENDDO
137     ENDDO
138     ENDDO
139     DO K=1,Nr
140     DO J=1,sNy
141     DO I=1,sNx
142     phiTotal(I,J,K) = phiTotal(I,J,K) +
143     & recip_rhoConst*(phi_hyd(i,j,k,bi,bj))
144     ENDDO
145     ENDDO
146     ENDDO
147     DO J=1,sNy
148     DO I=1,sNx
149     phiTSum = phiTSum + phiTotal(I,J,Nr)
150     ENDDO
151     ENDDO
152     ans = phiTCount
153     C _GLOBAL_SUM_R8( phiTCount, myThid )
154     phiTcount = ans
155     ans = phiTSum
156     C _GLOBAL_SUM_R8( phiTSum, myThid )
157     phiTSum = ans
158     C ptotalniv5=phiTSum/phiTCount
159     ptotalniv5=0.
160    
161     C Note the mapping here is only valid for one tile
162     C per proc.
163     DO K = 1, Nr
164     DO J = 1, sNy
165     DO I = 1, sNx
166     I2 = (sNx)*(J-1)+I
167     Katm = _KD2KA( K )
168     UG1(I2,Katm) = 0.5*(uVel(I,J,K,bi,bj)+uVel(I+1,J,K,bi,bj))
169     VG1(I2,Katm) = 0.5*(vVel(I,J,K,bi,bj)+vVel(I,J+1,K,bi,bj))
170     C Phyiscs works with temperature - not potential temp.
171     TG1(I2,Katm) = theta(I,J,K,bi,bj)/((pGround/pSurfs(K))**(RD/CPAIR))
172     QG1(I2,Katm) = salt(I,J,K,bi,bj)
173     PHIG1(I2,Katm) = (phiTotal(I,J,K)- ptotalniv5 ) + gravity*Hinitial(k)
174     if(hFacC(i,j,k,bi,bj).eq.1.) then
175     RHOG1(I2,Katm) = pSurfs(K)/RD/TG1(I2,Katm)
176     else
177     RHOG1(I2,Katm)=0.
178     endif
179     ENDDO
180     ENDDO
181     ENDDO
182    
183     C
184     C Set geopotential surfaces
185     C -------------------------
186     DO J=1,sNy
187     DO I=1,sNx
188     I2 = (sNx)*(J-1)+I
189     IF ( Nlevxy(I2) .NE. 0 ) THEN
190     PHI0(I2) = gravity*Hinitialw(Nlevxy(I2))
191     ELSE
192     PHI0(I2) = 0.
193     ENDIF
194     ENDDO
195     ENDDO
196     C
197     C Physics package works with log of surface pressure
198     C Get surface pressure from pbot-dpref/dz*Z'
199     DO J=1,sNy
200     DO I=1,sNx
201     I2 = (sNx)*(J-1)+I
202     IF ( Nlevxy(I2) .NE. 0 ) THEN
203     PNLEVW(I2) = PsurfW(Nlevxy(I2))/pGround
204     ELSE
205     C Dummy value for land
206     PNLEVW(I2) = PsurfW(1)/pGround
207     ENDIF
208     PSLG1(I2) = 0.
209     ENDDO
210     ENDDO
211     cch write(0,*) '(PNLEVW(I2),I2=257,384)'
212     cch write(0,*) (PNLEVW(I2),I2=257,384)
213     C
214     C
215     C Physics package needs to know time of year as a fraction
216     tYear = currentTime/(86400.*360.) -
217     & FLOAT(INT(currentTime/(86400.*360.)))
218     C
219     C Load external data needed by physics package
220     C 1. Albedo
221     C 2. Soil moisture
222     C 3. Surface temperatures
223     C 4. Snow depth - assume no snow for now
224     C 5. Sea ice - assume no sea ice for now
225     C 6. Land sea mask - infer from exact zeros in soil moisture dataset
226     C 7. Surface geopotential - to be done when orography is in
227     C dynamical kernel. Assume 0. for now.
228     mnthIndex = INT(tYear*12.)+1
229     IF ( mnthIndex .NE. prevMnthIndex .OR.
230     & FirstCall ) THEN
231     prevMnthIndex = mnthIndex
232     C Read in surface albedo data (input is in % 0-100 )
233     C scale to give fraction between 0-1 for Francos package.
234     CequChan WRITE(fNam,'(A,A,A)' ) 'salb.',mnthNam(mnthIndex),'.sun.b'
235     CequChan OPEN(1,FILE=fNam(1:14),STATUS='old',FORM='unformatted')
236     CequChan READ(1) tmp4
237     CequChan CLOSE(1)
238     CequChan DO J=1,nYio
239     CequChan DO I=1,nXio
240     CequChan tmp4(I,J) = tmp4(I,J)/100.
241     CequChan ENDDO
242     CequChan ENDDO
243     DO J=1,sNy
244     DO I=1,sNx
245     I2 = (sNx)*(J-1)+I
246     alb0(I2) = 0.
247     CequChan IF ( IG0+I-1 .LE. nxIo .AND. JG0+J-1 .LE. nyIo ) THEN
248     CequChan alb0(I2) = tmp4(IG0+I-1,JG0+J-1)
249     CequChan ENDIF
250     ENDDO
251     ENDDO
252     C Read in surface temperature data (input is in absolute temperature)
253     CequChan WRITE(fNam,'(A,A,A)' ) 'tsurf.',mnthNam(mnthIndex),'.sun.b'
254     CequChan OPEN(1,FILE=fNam(1:15),STATUS='old',FORM='unformatted')
255     CequChan READ(1) tmp4
256     CequChan CLOSE(1)
257     DO J=1,sNy
258     DO I=1,sNx
259     I2 = (sNx)*(J-1)+I
260     sst1(I2) = 300.
261     stl1(I2) = 300.
262     CequChan IF ( IG0+I-1 .LE. nxIo .AND. JG0+J-1 .LE. nyIo ) THEN
263     CequChan sst1(I2) = tmp4(IG0+I-1,JG0+J-1)
264     CequChan stl1(I2) = tmp4(IG0+I-1,JG0+J-1)
265     CequChan ENDIF
266     caja IF ( I .GE. 64-10 .AND. I .LE. 65+10 ) THEN
267     caja sst1(I2) = 310.
268     caja stl1(I2) = 310.
269     caja ENDIF
270     caja IF ( I .GE. 64-10 .AND. I .LE. 65+10 ) THEN
271     caja sst1(I2) = 300.+10.*exp( -((float(I)-64.5)/5.)**2 )
272     caja stl1(I2) = sst1(I2)
273     caja ENDIF
274     c_jmc: should not be part of the AIM package :
275     sst1(I2) = 300.+10.*exp( -((float(I)-64.5)/25.)**2 )
276     stl1(I2) = sst1(I2)
277     ENDDO
278     ENDDO
279     C
280     C Read in soil moisture data (input is in cm in bucket of depth 20cm. )
281     C??? NOT CLEAR scale for bucket depth of 75mm which is what Franco uses.
282     CequChan WRITE(fNam,'(A,A,A)' ) 'smoist.',mnthNam(mnthIndex),'.sun.b'
283     CequChan OPEN(1,FILE=fNam(1:16),STATUS='old',FORM='unformatted')
284     CequChan READ(1) tmp4
285     CequChan CLOSE(1)
286     CequChan WRITE(0,*) ' Read file ', fNam(1:16), IG0, JG0
287     cdj tmp4 = (tmp4*7.5/20.)*10.
288     DO J=1,sNy
289     DO I=1,sNx
290     I2 = (sNx)*(J-1)+I
291     soilq1(I2) = 0.
292     CequChan IF ( IG0+I-1 .LE. nxIo .AND. JG0+J-1 .LE. nyIo ) THEN
293     CequChan soilq1(I2) = tmp4(IG0+I-1,JG0+J-1)
294     CequChan ENDIF
295     ENDDO
296     ENDDO
297     cdj Soilqmax=MAxval(soilq1)
298     Soilqmax=20.
299     cdj if(Soilqmax.ne.0.) then
300     DO J=1,sNy
301     DO I=1,sNx
302     I2 = (sNx)*(J-1)+I
303     CequChan soilq1(I2)=soilq1(I2)/Soilqmax
304     soilq1(I2) = 1.
305     ENDDO
306     ENDDO
307     cdj endif
308     ENDIF
309     C
310     IF ( FirstCall ) THEN
311     C Set snow depth, sea ice to zero for now
312     C Land-sea mask ( figure this out from where soil moisture is exactly zero ).
313     DO J=1,sNy
314     DO I=1,sNx
315     I2 = (sNx)*(J-1)+I
316     fMask1(I2) = 1.
317     IF ( soilq1(I2) .EQ. 0. ) fMask1(I2) = 0.
318     oice1(I2) = 0.
319     snow1(I2) = 0.
320     ENDDO
321     ENDDO
322     C open(77,file='lsmask',form='unformatted')
323     C write(77) fmask1
324     C close(77)
325     ENDIF
326     C
327     C Addition may 15 . Reset humidity to 0. if negative
328     C ---------------------------------------------------
329     DO K=1,Nr
330     DO J=1-OLy,sNy+OLy
331     DO I=1-Olx,sNx+OLx
332     IF ( salt(i,j,k,bi,bj) .LT. 0. .OR. K .EQ. Nr ) THEN
333     salt(i,j,k,bi,bj) = 0.
334     ENDIF
335     ENDDO
336     ENDDO
337     ENDDO
338     C
339     CALL PDRIVER( tYear )
340    
341 jmc 1.3 #ifdef ALLOW_TIMEAVE
342 adcroft 1.2 C Calculate diagnostics for AIM
343     CALL AIM_CALC_DIAGS( bi, bj, currentTime, myThid )
344 jmc 1.3 #endif /* ALLOW_TIMEAVE */
345 adcroft 1.2 C
346     FirstCall = .FALSE.
347     C
348     #endif /* ALLOW_AIM */
349    
350     RETURN
351     END

  ViewVC Help
Powered by ViewVC 1.1.22