/[MITgcm]/MITgcm/pkg/cheapaml/cheapaml_fields_load.F
ViewVC logotype

Contents of /MITgcm/pkg/cheapaml/cheapaml_fields_load.F

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


Revision 1.1 - (show annotations) (download)
Tue Aug 5 21:49:31 2008 UTC (15 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61c
From Nicolas: new package, (Cheap) Atmospheric Mixed Layer

1 C $Header: /u/gcmpack/MITgcm/pkg/bulk_force/bulkf_fields_load.F,v 1.10 2005/04/06 18:36:22 jmc Exp $
2 C $Name: $
3 #include "CHEAPAML_OPTIONS.h"
4
5 C !ROUTINE: CHEAPAML_FIELDS_LOAD
6 C !INTERFACE:
7 SUBROUTINE CHEAPAML_FIELDS_LOAD( myTime, myIter, myThid )
8 C *==========================================================*
9 C | SUBROUTINE CHEAPAML_FIELDS_LOAD
10 C | o Control reading of fields from external source.
11 C *==========================================================*
12
13 C !USES:
14 IMPLICIT NONE
15 C === Global variables ===
16 #include "SIZE.h"
17 #include "EEPARAMS.h"
18 #include "PARAMS.h"
19 #include "FFIELDS.h"
20 c #include "GRID.h"
21 c #include "DYNVARS.h"
22 C #include "BULKF.h"
23 #ifdef ALLOW_THSICE
24 #include "THSICE_VARS.h"
25 #endif
26 #include "CHEAPAML.h"
27
28 C !INPUT/OUTPUT PARAMETERS:
29 C === Routine arguments ===
30 C myThid - Thread no. that called this routine.
31 C myTime - Simulation time
32 C myIter - Simulation timestep number
33 C dsolms - Solar variation at Southern boundary
34 C dsolmn - Solar variation at Northern boundary
35 c xphaseinit - user input initial phase of year relative
36 c to mid winter. E.G. xphaseinit = pi implies time zero
37 c is mid summer.
38 INTEGER myThid
39 _RL myTime
40 _RL local ,bump
41 c _RL dsolms,dsolmn
42 c _RL xphaseinit
43 INTEGER myIter
44 INTEGER jg
45
46 C !LOCAL VARIABLES:
47 C === Local arrays ===
48 C trair[01] :: Relaxation temp. profile for air temperature
49 C qrair[01] :: Relaxation specific humidity profile for air
50 C solar[01] :: short wave flux
51 C uwind[01] :: zonal wind
52 C vwind[01] :: meridional wind
53
54 C aWght, bWght :: Interpolation weights
55 COMMON /BULKFFIELDS/
56 & trair0,
57 & trair1,
58 & qrair0,
59 & qrair1
60
61 _RS trair0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
62 _RS trair1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
63 _RS qrair0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
64 _RS qrair1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
65 _RS Solar0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
66 _RS Solar1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
67 _RS uwind0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
68 _RS uwind1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
69 _RS vwind0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
70 _RS vwind1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
71
72 INTEGER bi,bj,i,j,intime0,intime1
73 _RL aWght,bWght,rdt
74 _RL ssq0,ssq1,ssq2,lath,p0,ssqa,q
75 c xsolph - phase of year, assuming time zero is mid winter
76 c xinxx - cos ( xsolph )
77 _RL xsolph,xinxx
78 INTEGER nForcingPeriods,Imytm,Ifprd,Ifcyc,Iftm
79 c coefficients used to compute saturation specific humidity
80 DATA ssq0, ssq1, ssq2
81 & / 3.797915 _d 0 , 7.93252 _d -6 , 2.166847 _d -3 /
82
83 c latent heat (J/kg)
84 lath=2.5d6
85 c sea level pressure
86 p0=1000.d0
87
88 IF ( periodicExternalForcing ) THEN
89
90 write(*,*) 'TEST 1 ========================='
91
92 c the objective here is to give cheapaml a default periodic forcing
93 c consisting only of annually varying solar forcing, and thus Trelaxation
94 c variation. everything else, relative humidity, wind, are fixed. This
95 c keys off of solardata. if a solar data file exists, the model will
96 c assume there are files to be read and interpolated between, as is standard
97 c for the MITGCM.
98
99 IF ( SolarFile .EQ. ' ' ) THEN
100 if ( myIter .EQ. nIter0 )then
101 WRITE(*,*)
102 & 'S/R Assuming Standard Annually Varying Solar Forcing'
103 endif
104 xsolph=myTime*2.d0*3.14159 _d 0/365. _d 0/86400. _d 0
105 xinxx=cos(xsolph+xphaseinit+3.14159 _d 0)
106 DO bj=1,nSy
107 DO bi=1,nSx
108 DO j=1,sNy
109 DO i=1,sNx
110 jG = myYGlobalLo-1+(bj-1)*sNy+j
111 local=225.d0+dsolms*xinxx-float((jg-1))/float((ny-1))*
112 & (37.5d0-dsolmn*xinxx)
113 if ( jG .le. 3 ) local = local + 200
114 Solar(i,j,bi,bj) = local
115 ENDDO
116 ENDDO
117 ENDDO
118 ENDDO
119 _EXCH_XY_RS(solar, mythid)
120 c relaxation temperature in radiative equilibrium
121 DO bj=1,nSy
122 DO bi=1,nSx
123 DO j=1,sNy
124 DO i=1,sNx
125 jG = myYGlobalLo-1+(bj-1)*sNy+j
126 local=solar(i,j,bi,bj)
127 local=(2.d0*local/stefan)**(0.25d0)-273.16
128 bump=-5.d0*EXP(-(float(jg-127)*float(jg-127))/1920.0)
129 local=local+bump
130 TR(i,j,bi,bj) = local
131 ENDDO
132 ENDDO
133 ENDDO
134 ENDDO
135 _EXCH_XY_RS(TR, mythid)
136 c default specific humidity profile to 80% relative humidity
137 DO bj=1,nSy
138 DO bi=1,nSx
139 DO j=1,sNy
140 DO i=1,sNx
141 c jG = myYGlobalLo-1+(bj-1)*sNy+j
142 local = Tr(i,j,bi,bj)+273.16d0
143 ssqa = ssq0*exp( lath*(ssq1-ssq2/local)) / p0
144 qr(i,j,bi,bj) = 0.8d0*ssqa
145 ENDDO
146 ENDDO
147 ENDDO
148 ENDDO
149 _EXCH_XY_RS(qr, mythid)
150 c u wind field
151 DO bj=1,nSy
152 DO bi=1,nSx
153 DO j=1,sNy
154 DO i=1,sNx
155 jG = myYGlobalLo-1+(bj-1)*sNy+j
156 local=-5.d0*cos(2.d0*pi*float(jg-1)/(float(ny-1)))
157 uwind(i,j,bi,bj) = local
158 ENDDO
159 ENDDO
160 ENDDO
161 ENDDO
162 _EXCH_XY_RS(uwind, mythid)
163 c v wind field
164 DO bj=1,nSy
165 DO bi=1,nSx
166 DO j=1,sNy
167 DO i=1,sNx
168 jG = myYGlobalLo-1+(bj-1)*sNy+j
169 vwind(i,j,bi,bj) = 0.d0
170 ENDDO
171 ENDDO
172 ENDDO
173 ENDDO
174 _EXCH_XY_RS(vwind, mythid)
175 else
176
177 c here for usual interpolative forcings
178 C First call requires that we initialize everything to zero for safety
179 IF ( myIter .EQ. nIter0 ) THEN
180 CALL LEF_ZERO( trair0 ,myThid )
181 CALL LEF_ZERO( trair1 ,myThid )
182 CALL LEF_ZERO( qrair0 ,myThid )
183 CALL LEF_ZERO( qrair1 ,myThid )
184 CALL LEF_ZERO( solar0 ,myThid )
185 CALL LEF_ZERO( solar1 ,myThid )
186 CALL LEF_ZERO( uwind0 ,myThid )
187 CALL LEF_ZERO( uwind1 ,myThid )
188 CALL LEF_ZERO( vwind0 ,myThid )
189 CALL LEF_ZERO( vwind1 ,myThid )
190 ENDIF
191
192 C Now calculate whether it is time to update the forcing arrays
193 rdt=1. _d 0 / deltaTclock
194 nForcingPeriods=
195 & int(externForcingCycle/externForcingPeriod+0.5)
196 Imytm=int(myTime*rdt+0.5)
197 Ifprd=int(externForcingPeriod*rdt+0.5)
198 Ifcyc=int(externForcingCycle*rdt+0.5)
199 Iftm=mod( Imytm+Ifcyc-Ifprd/2 ,Ifcyc)
200
201 intime0=int(Iftm/Ifprd)
202 intime1=mod(intime0+1,nForcingPeriods)
203 c aWght=float( Iftm-Ifprd*intime0 )/float( Ifprd )
204 aWght=dfloat( Iftm-Ifprd*intime0 )/dfloat( Ifprd )
205 bWght=1.-aWght
206
207 intime0=intime0+1
208 intime1=intime1+1
209
210 IF (
211 & Iftm-Ifprd*(intime0-1) .EQ. 0
212 & .OR. myIter .EQ. nIter0
213 & ) THEN
214
215 _BEGIN_MASTER(myThid)
216
217 C If the above condition is met then we need to read in
218 C data for the period ahead and the period behind myTime.
219 WRITE(*,*)
220 & 'S/R CHEAPAML_FIELDS_LOAD'
221 IF ( SolarFile .NE. ' ' ) THEN
222 CALL READ_REC_XY_RS( SolarFile,solar0,intime0,
223 & myIter,myThid )
224 CALL READ_REC_XY_RS( SolarFile,solar1,intime1,
225 & myIter,myThid )
226 ENDIF
227 IF ( TrFile .NE. ' ' ) THEN
228 CALL READ_REC_XY_RS( TRFile,trair0,intime0,
229 & myIter,myThid )
230 CALL READ_REC_XY_RS( TRFile,trair1,intime1,
231 & myIter,myThid )
232 ENDIF
233 IF ( QrFile .NE. ' ' ) THEN
234 CALL READ_REC_XY_RS( QrFile,qrair0,intime0,
235 & myIter,myThid )
236 CALL READ_REC_XY_RS( QrFile,qrair1,intime1,
237 & myIter,myThid )
238 ENDIF
239 IF ( UWindFile .NE. ' ' ) THEN
240 CALL READ_REC_XY_RS( UWindFile,uwind0,intime0,
241 & myIter,myThid )
242 CALL READ_REC_XY_RS( UWindFile,uwind1,intime1,
243 & myIter,myThid )
244 ENDIF
245 IF ( VWindFile .NE. ' ' ) THEN
246 CALL READ_REC_XY_RS( VWindFile,vwind0,intime0,
247 & myIter,myThid )
248 CALL READ_REC_XY_RS( VWindFile,vwind1,intime1,
249 & myIter,myThid )
250 ENDIF
251
252 _END_MASTER(myThid)
253 C
254 _EXCH_XY_R4(trair0 , myThid )
255 _EXCH_XY_R4(qrair0 , myThid )
256 _EXCH_XY_R4(solar0 , myThid )
257 _EXCH_XY_R4(uwind0 , myThid )
258 _EXCH_XY_R4(vwind0 , myThid )
259 _EXCH_XY_R4(trair1 , myThid )
260 _EXCH_XY_R4(qrair1 , myThid )
261 _EXCH_XY_R4(solar1 , myThid )
262 _EXCH_XY_R4(uwind1 , myThid )
263 _EXCH_XY_R4(vwind1 , myThid )
264 C
265 ENDIF
266
267 C-- Interpolate TR, QR, SOLAR
268 DO bj = myByLo(myThid), myByHi(myThid)
269 DO bi = myBxLo(myThid), myBxHi(myThid)
270 DO j=1-Oly,sNy+Oly
271 DO i=1-Olx,sNx+Olx
272 TR(i,j,bi,bj) = bWght*trair0(i,j,bi,bj)
273 & +aWght*trair1(i,j,bi,bj) !+273.15
274 qr(i,j,bi,bj) = bWght*qrair0(i,j,bi,bj)
275 & +aWght*qrair1(i,j,bi,bj)
276 uwind(i,j,bi,bj) = bWght*uwind0(i,j,bi,bj)
277 & +aWght*uwind1(i,j,bi,bj)
278 vwind(i,j,bi,bj) = bWght*vwind0(i,j,bi,bj)
279 & +aWght*vwind1(i,j,bi,bj)
280 solar(i,j,bi,bj) = bWght*solar0(i,j,bi,bj)
281 & +aWght*solar1(i,j,bi,bj)
282 ENDDO
283 ENDDO
284 ENDDO
285 ENDDO
286 endif
287 c end of periodic forcing options, on to steady option
288
289 ELSE
290 IF ( myIter .EQ. nIter0 ) THEN
291 IF ( SolarFile .NE. ' ' ) THEN
292 CALL READ_FLD_XY_RS( SolarFile,solar,' ',0,myThid )
293 ELSE
294 DO bj=1,nSy
295 DO bi=1,nSx
296 DO j=1,sNy
297 DO i=1,sNx
298 jG = myYGlobalLo-1+(bj-1)*sNy+j
299 local=225.d0-float((jg-1))/float((ny-1))*37.5d0
300 IF ( jG .le. 3 ) local =local + 200
301 Solar(i,j,bi,bj) = local
302 ENDDO
303 ENDDO
304 ENDDO
305 ENDDO
306 _EXCH_XY_RS(solar, mythid)
307 ENDIF
308 IF ( TrFile .NE. ' ' ) THEN
309 CALL READ_FLD_XY_RS( TrFile,tr,' ',0,myThid )
310 ELSE
311 DO bj=1,nSy
312 DO bi=1,nSx
313 DO j=1,sNy
314 DO i=1,sNx
315 jG = myYGlobalLo-1+(bj-1)*sNy+j
316 local=solar(i,j,bi,bj)
317 local=(2.d0*local/stefan)**(0.25d0)-273.16
318 bump=-5.d0*EXP(-(float(jg-127)*float(jg-127))/1920.0)
319 local=local+bump
320 TR(i,j,bi,bj) = local
321 ENDDO
322 ENDDO
323 ENDDO
324 ENDDO
325 _EXCH_XY_RS(TR, mythid)
326 ENDIF
327 c do specific humidity
328 IF ( QrFile .NE. ' ' ) THEN
329 CALL READ_FLD_XY_RS( QrFile,qr,' ',0,myThid )
330 ELSE
331 c default specific humidity profile to 80% relative humidity
332 DO bj=1,nSy
333 DO bi=1,nSx
334 DO j=1,sNy
335 DO i=1,sNx
336 c jG = myYGlobalLo-1+(bj-1)*sNy+j
337 local = Tr(i,j,bi,bj)+273.16d0
338 ssqa = ssq0*exp( lath*(ssq1-ssq2/local)) / p0
339 qr(i,j,bi,bj) = 0.8d0*ssqa
340 ENDDO
341 ENDDO
342 ENDDO
343 ENDDO
344 _EXCH_XY_RS(qr, mythid)
345 ENDIF
346 IF ( UWindFile .NE. ' ' ) THEN
347 CALL READ_FLD_XY_RS( UWindFile,uwind,' ',0,myThid )
348 ELSE
349 DO bj=1,nSy
350 DO bi=1,nSx
351 DO j=1,sNy
352 DO i=1,sNx
353 jG = myYGlobalLo-1+(bj-1)*sNy+j
354 c mod for debug
355 c to return to original code, uncomment following line
356 c comment out 2nd line
357 local=-5.d0*cos(2.d0*pi*float(jg-1)/(float(ny-1)))
358 c local=0.d0*cos(2.d0*pi*float(jg-1)/(float(ny-1)))
359 uwind(i,j,bi,bj) = local
360 ENDDO
361 ENDDO
362 ENDDO
363 ENDDO
364 _EXCH_XY_RS(uwind, mythid)
365 ENDIF
366 IF ( VWindFile .NE. ' ' ) THEN
367 CALL READ_FLD_XY_RS( VWindFile,vwind,' ',0,myThid )
368 ELSE
369 DO bj=1,nSy
370 DO bi=1,nSx
371 DO j=1,sNy
372 DO i=1,sNx
373 jG = myYGlobalLo-1+(bj-1)*sNy+j
374 vwind(i,j,bi,bj) = 0.d0
375 ENDDO
376 ENDDO
377 ENDDO
378 ENDDO
379 _EXCH_XY_RS(vwind, mythid)
380 ENDIF
381 ENDIF
382 C endif for periodicForcing
383 ENDIF
384
385 RETURN
386 END

  ViewVC Help
Powered by ViewVC 1.1.22