/[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.7 - (show annotations) (download)
Sun Feb 6 00:18:05 2011 UTC (13 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62s
Changes since 1.6: +429 -216 lines
From Nico Wienders: Updated version of this package.

1 C $Header: /u/gcmpack/MITgcm/pkg/cheapaml/cheapaml_fields_load.F,v 1.4 2009/04/28 18:08:13 jmc Exp $
2 C $Name: $
3
4 #include "CHEAPAML_OPTIONS.h"
5
6 C !ROUTINE: CHEAPAML_FIELDS_LOAD
7 C !INTERFACE:
8 SUBROUTINE CHEAPAML_FIELDS_LOAD( myTime, myIter, myThid )
9 C *==========================================================*
10 C | SUBROUTINE CHEAPAML_FIELDS_LOAD
11 C | o Control reading of fields from external source.
12 C *==========================================================*
13
14 C !USES:
15 IMPLICIT NONE
16 C === Global variables ===
17 #include "SIZE.h"
18 #include "EEPARAMS.h"
19 #include "PARAMS.h"
20 #include "FFIELDS.h"
21 c #include "GRID.h"
22 c #include "DYNVARS.h"
23 C #include "BULKF.h"
24 c #ifdef ALLOW_THSICE
25 c #include "THSICE_VARS.h"
26 c #endif
27 #include "CHEAPAML.h"
28
29 C !INPUT/OUTPUT PARAMETERS:
30 C === Routine arguments ===
31 C myThid - Thread no. that called this routine.
32 C myTime - Simulation time
33 C myIter - Simulation timestep number
34 C dsolms - Solar variation at Southern boundary
35 C dsolmn - Solar variation at Northern boundary
36 c xphaseinit - user input initial phase of year relative
37 c to mid winter. E.G. xphaseinit = pi implies time zero
38 c is mid summer.
39 INTEGER myThid
40 _RL myTime
41 _RL local
42 c _RL dsolms,dsolmn
43 c _RL xphaseinit
44 INTEGER myIter
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 C aWght, bWght :: Interpolation weights
54
55 COMMON /BULKFFIELDS/
56 & trair0, trair1,
57 & qrair0, qrair1,
58 & Solar0, Solar1,
59 & uwind0, uwind1,
60 & vwind0, vwind1,
61 & ustress0, ustress1,
62 & vstress0, vstress1,
63 & wavesh0, wavesh1,
64 & wavesp0, wavesp1,
65 & rair0, rair1
66
67 _RL trair0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
68 _RL trair1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
69 _RL qrair0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
70 _RL qrair1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
71 _RL Solar0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
72 _RL Solar1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
73 _RL uwind0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
74 _RL uwind1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
75 _RL vwind0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
76 _RL vwind1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
77 _RL ustress0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
78 _RL ustress1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
79 _RL vstress0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
80 _RL vstress1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
81 _RL wavesh0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
82 _RL wavesh1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
83 _RL wavesp0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
84 _RL wavesp1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
85 _RL rair0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
86 _RL rair1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
87
88 INTEGER bi,bj,i,j,intime0,intime1
89 INTEGER iG,jG
90 _RL aWght,bWght,rdt,u
91 _RL ssq0,ssq1,ssq2,ssqa
92 c xsolph - phase of year, assuming time zero is mid winter
93 c xinxx - cos ( xsolph )
94 _RL xsolph,xinxx
95 INTEGER nForcingPeriods,Imytm,Ifprd,Ifcyc,Iftm
96 c coefficients used to compute saturation specific humidity
97 DATA ssq0, ssq1, ssq2
98 & / 3.797915 _d 0 , 7.93252 _d -6 , 2.166847 _d -3 /
99
100 IF ( periodicExternalForcing ) THEN
101
102 c the objective here is to give cheapaml a default periodic forcing
103 c consisting only of annually varying solar forcing, and thus Trelaxation
104 c variation. everything else, relative humidity, wind, are fixed. This
105 c keys off of solardata. if a solar data file exists, the model will
106 c assume there are files to be read and interpolated between, as is standard
107 c for the MITGCM.
108
109 IF ( SolarFile .EQ. ' ' ) THEN
110 IF (useStressOption)then
111 write(*,*)' stress option is turned on. this is not',
112 & 'consistent with the default time dependent forcing option'
113 STOP 'ABNORMAL END: S/R CHEAPAML_FIELDS_LOAD'
114 ENDIF
115 if ( myIter .EQ. nIter0 )then
116 WRITE(*,*)
117 & 'S/R Assuming Standard Annually Varying Solar Forcing'
118 endif
119 xsolph=myTime*2.d0*3.14159 _d 0/365. _d 0/86400. _d 0
120 xinxx=cos(xsolph+xphaseinit+3.14159 _d 0)
121 DO bj = myByLo(myThid), myByHi(myThid)
122 DO bi = myBxLo(myThid), myBxHi(myThid)
123 DO j=1,sNy
124 DO i=1,sNx
125 jG = myYGlobalLo-1+(bj-1)*sNy+j
126 local=225.d0+dsolms*xinxx-float((jg-1))/float((ny-1))*
127 & (37.5d0-dsolmn*xinxx)
128 Solar(i,j,bi,bj) = local
129 ENDDO
130 ENDDO
131 ENDDO
132 ENDDO
133 _EXCH_XY_RL(solar, myThid)
134 c relaxation temperature in radiative equilibrium
135 DO bj = myByLo(myThid), myByHi(myThid)
136 DO bi = myBxLo(myThid), myBxHi(myThid)
137 DO j=1,sNy
138 DO i=1,sNx
139 jG = myYGlobalLo-1+(bj-1)*sNy+j
140 local=solar(i,j,bi,bj)
141 local=(2.d0*local/stefan)**(0.25d0)-Celcius2K
142 Tr(i,j,bi,bj) = local
143 ENDDO
144 ENDDO
145 ENDDO
146 ENDDO
147 _EXCH_XY_RL(Tr, myThid)
148 c default specific humidity profile to 80% relative humidity
149 DO bj = myByLo(myThid), myByHi(myThid)
150 DO bi = myBxLo(myThid), myBxHi(myThid)
151 DO j=1,sNy
152 DO i=1,sNx
153 c jG = myYGlobalLo-1+(bj-1)*sNy+j
154 local = Tr(i,j,bi,bj)+Celcius2K
155 ssqa = ssq0*exp( lath*(ssq1-ssq2/local)) / p0
156 qr(i,j,bi,bj) = 0.8d0*ssqa
157 ENDDO
158 ENDDO
159 ENDDO
160 ENDDO
161 _EXCH_XY_RL(qr, myThid)
162 c u wind field
163 DO bj = myByLo(myThid), myByHi(myThid)
164 DO bi = myBxLo(myThid), myBxHi(myThid)
165 DO j=1,sNy
166 DO i=1,sNx
167 jG = myYGlobalLo-1+(bj-1)*sNy+j
168 local=-5.d0*cos(2.d0*pi*float(jg-1)/(float(ny-1)))
169 uwind(i,j,bi,bj) = local
170 ENDDO
171 ENDDO
172 ENDDO
173 ENDDO
174 _EXCH_XY_RL(uwind, myThid)
175 c v wind field
176 DO bj = myByLo(myThid), myByHi(myThid)
177 DO bi = myBxLo(myThid), myBxHi(myThid)
178 DO j=1,sNy
179 DO i=1,sNx
180 jG = myYGlobalLo-1+(bj-1)*sNy+j
181 vwind(i,j,bi,bj) = 0.d0
182 ENDDO
183 ENDDO
184 ENDDO
185 ENDDO
186 _EXCH_XY_RL(vwind, myThid)
187
188 ELSE
189 C else: solarFile non empty
190
191 C here for usual interpolative forcings
192 C First call requires that we initialize everything to zero for safety
193 IF ( myIter .EQ. nIter0 ) THEN
194 DO bj = myByLo(myThid), myByHi(myThid)
195 DO bi = myBxLo(myThid), myBxHi(myThid)
196 DO j=1-OLy,sNy+OLy
197 DO i=1-OLx,sNx+OLx
198 trair0 (i,j,bi,bj) = 0.
199 trair1 (i,j,bi,bj) = 0.
200 qrair0 (i,j,bi,bj) = 0.
201 qrair1 (i,j,bi,bj) = 0.
202 solar0 (i,j,bi,bj) = 0.
203 solar1 (i,j,bi,bj) = 0.
204 uwind0 (i,j,bi,bj) = 0.
205 uwind1 (i,j,bi,bj) = 0.
206 vwind0 (i,j,bi,bj) = 0.
207 vwind1 (i,j,bi,bj) = 0.
208 ustress0(i,j,bi,bj) = 0.
209 ustress1(i,j,bi,bj) = 0.
210 vstress0(i,j,bi,bj) = 0.
211 vstress1(i,j,bi,bj) = 0.
212 wavesh0 (i,j,bi,bj) = 0.
213 wavesh1 (i,j,bi,bj) = 0.
214 wavesp0 (i,j,bi,bj) = 0.
215 wavesp1 (i,j,bi,bj) = 0.
216 rair0 (i,j,bi,bj) = 0.
217 rair1 (i,j,bi,bj) = 0.
218 ENDDO
219 ENDDO
220 ENDDO
221 ENDDO
222 ENDIF
223
224 C Now calculate whether it is time to update the forcing arrays
225 rdt=1. _d 0 / deltaTclock
226 nForcingPeriods=
227 & int(externForcingCycle/externForcingPeriod+0.5)
228 Imytm=int(myTime*rdt+0.5)
229 Ifprd=int(externForcingPeriod*rdt+0.5)
230 Ifcyc=int(externForcingCycle*rdt+0.5)
231 Iftm=mod( Imytm+Ifcyc-Ifprd/2 ,Ifcyc)
232
233 intime0=int(Iftm/Ifprd)
234 intime1=mod(intime0+1,nForcingPeriods)
235 c aWght=float( Iftm-Ifprd*intime0 )/float( Ifprd )
236 aWght=dfloat( Iftm-Ifprd*intime0 )/dfloat( Ifprd )
237 bWght=1.-aWght
238
239 intime0=intime0+1
240 intime1=intime1+1
241
242 IF (
243 & Iftm-Ifprd*(intime0-1) .EQ. 0
244 & .OR. myIter .EQ. nIter0
245 & ) THEN
246
247 C If the above condition is met then we need to read in
248 C data for the period ahead and the period behind myTime.
249 WRITE(*,*)
250 & 'S/R CHEAPAML_FIELDS_LOAD'
251 IF ( SolarFile .NE. ' ' ) THEN
252 CALL READ_REC_XY_RL( SolarFile,solar0,intime0,
253 & myIter,myThid )
254 CALL READ_REC_XY_RL( SolarFile,solar1,intime1,
255 & myIter,myThid )
256 ENDIF
257 IF ( TrFile .NE. ' ' ) THEN
258 CALL READ_REC_XY_RL( TrFile,trair0,intime0,
259 & myIter,myThid )
260 CALL READ_REC_XY_RL( TrFile,trair1,intime1,
261 & myIter,myThid )
262 ENDIF
263 IF ( QrFile .NE. ' ' ) THEN
264 CALL READ_REC_XY_RL( QrFile,qrair0,intime0,
265 & myIter,myThid )
266 CALL READ_REC_XY_RL( QrFile,qrair1,intime1,
267 & myIter,myThid )
268 ENDIF
269 IF ( UWindFile .NE. ' ' ) THEN
270 CALL READ_REC_XY_RL( UWindFile,uwind0,intime0,
271 & myIter,myThid )
272 CALL READ_REC_XY_RL( UWindFile,uwind1,intime1,
273 & myIter,myThid )
274 ENDIF
275 IF ( VWindFile .NE. ' ' ) THEN
276 CALL READ_REC_XY_RL( VWindFile,vwind0,intime0,
277 & myIter,myThid )
278 CALL READ_REC_XY_RL( VWindFile,vwind1,intime1,
279 & myIter,myThid )
280 ENDIF
281 IF(useStressOption)THEN
282 IF ( UStressFile .NE. ' ' ) THEN
283 CALL READ_REC_XY_RL( UStressFile,ustress0,intime0,
284 & myIter,myThid )
285 CALL READ_REC_XY_RL( UStressFile,ustress1,intime1,
286 & myIter,myThid )
287 ENDIF
288 IF ( VStressFile .NE. ' ' ) THEN
289 CALL READ_REC_XY_RL( VStressFile,vstress0,intime0,
290 & myIter,myThid )
291 CALL READ_REC_XY_RL( VStressFile,vstress1,intime1,
292 & myIter,myThid )
293 ENDIF
294 ENDIF
295 IF(useRelativeHumidity)THEN
296 IF ( QrrelFile .NE. ' ' ) THEN
297 CALL READ_REC_XY_RL( QrrelFile,rair0,intime0,
298 & myIter,myThid )
299 CALL READ_REC_XY_RL( QrrelFile,rair1,intime1,
300 & myIter,myThid )
301 ENDIF
302 C This subroutine is in cheapaml_init_varia
303 CALL CHEAPAML_CONVERT_HUM(rair0, trair0, qrair0,myThid )
304 CALL CHEAPAML_CONVERT_HUM(rair1, trair1, qrair1,myThid )
305 ENDIF
306 IF ( FluxFormula.EQ.'COARE3') THEN
307 IF ( WaveHFile .NE. ' ' ) THEN
308 CALL READ_REC_XY_RL( WaveHFile,wavesh0,intime0,
309 & myIter,myThid )
310 CALL READ_REC_XY_RL( WaveHFile,wavesh1,intime1,
311 & myIter,myThid )
312 ENDIF
313 IF ( WavePFile .NE. ' ' ) THEN
314 CALL READ_REC_XY_RL( WavePFile,wavesp0,intime0,
315 & myIter,myThid )
316 CALL READ_REC_XY_RL( WavePFile,wavesp1,intime1,
317 & myIter,myThid )
318 ENDIF
319 ENDIF
320
321 _EXCH_XY_RL( trair0 , myThid )
322 _EXCH_XY_RL( qrair0 , myThid )
323 _EXCH_XY_RL( solar0 , myThid )
324 _EXCH_XY_RL( uwind0 , myThid )
325 _EXCH_XY_RL( vwind0 , myThid )
326 _EXCH_XY_RL( trair1 , myThid )
327 _EXCH_XY_RL( qrair1 , myThid )
328 _EXCH_XY_RL( solar1 , myThid )
329 _EXCH_XY_RL( uwind1 , myThid )
330 _EXCH_XY_RL( vwind1 , myThid )
331 IF(useStressOption)THEN
332 _EXCH_XY_RL( ustress0 , myThid )
333 _EXCH_XY_RL( vstress0 , myThid )
334 _EXCH_XY_RL( ustress1 , myThid )
335 _EXCH_XY_RL( vstress1 , myThid )
336 ENDIF
337 IF(FluxFormula.EQ.'COARE3') THEN
338 _EXCH_XY_RL( wavesp0 , myThid )
339 _EXCH_XY_RL( wavesp1 , myThid )
340 _EXCH_XY_RL( wavesh0 , myThid )
341 _EXCH_XY_RL( wavesh1 , myThid )
342 ENDIF
343
344 C end of loading new fields block
345 ENDIF
346
347 C-- Interpolate Tr, Qr, Solar
348 DO bj = myByLo(myThid), myByHi(myThid)
349 DO bi = myBxLo(myThid), myBxHi(myThid)
350 DO j=1,sNy
351 DO i=1,sNx
352 Tr(i,j,bi,bj) = bWght*trair0(i,j,bi,bj)
353 & +aWght*trair1(i,j,bi,bj) !+273.15
354 qr(i,j,bi,bj) = bWght*qrair0(i,j,bi,bj)
355 & +aWght*qrair1(i,j,bi,bj)
356 uwind(i,j,bi,bj)= bWght*uwind0(i,j,bi,bj)
357 & +aWght*uwind1(i,j,bi,bj)
358 vwind(i,j,bi,bj)= bWght*vwind0(i,j,bi,bj)
359 & +aWght*vwind1(i,j,bi,bj)
360 solar(i,j,bi,bj)= bWght*solar0(i,j,bi,bj)
361 & +aWght*solar1(i,j,bi,bj)
362 IF(useStressOption)THEN
363 ustress(i,j,bi,bj)= bWght*ustress0(i,j,bi,bj)
364 & +aWght*ustress1(i,j,bi,bj)
365 vstress(i,j,bi,bj)= bWght*vstress0(i,j,bi,bj)
366 & +aWght*vstress1(i,j,bi,bj)
367 ENDIF
368 IF(FluxFormula.EQ.'COARE3')THEN
369 IF(WaveHFile.NE.' ')THEN
370 wavesh(i,j,bi,bj) = bWght*wavesh0(i,j,bi,bj)
371 & +aWght*wavesh1(i,j,bi,bj)
372 ENDIF
373 IF(WavePFile.NE.' ')THEN
374 wavesp(i,j,bi,bj) = bWght*wavesp0(i,j,bi,bj)
375 & +aWght*wavesp1(i,j,bi,bj)
376 ENDIF
377 ELSE
378 u=uwind(i,j,bi,bj)**2+vwind(i,j,bi,bj)**2
379 u=dsqrt(u)
380 wavesp(i,j,bi,bj)=0.729 _d 0 * u
381 wavesh(i,j,bi,bj)=0.018 _d 0 * u*u*(1. _d 0 + .015 _d 0 *u)
382 ENDIF
383 ENDDO
384 ENDDO
385 ENDDO
386 ENDDO
387
388 C end if solarFile is empty
389 ENDIF
390
391 C end of periodic forcing options, on to steady option
392 ELSE
393
394 IF ( myIter .EQ. nIter0 ) THEN
395 IF ( SolarFile .NE. ' ' ) THEN
396 CALL READ_FLD_XY_RL( SolarFile,' ',solar,0,myThid )
397 ELSE
398 DO bj = myByLo(myThid), myByHi(myThid)
399 DO bi = myBxLo(myThid), myBxHi(myThid)
400 DO j=1,sNy
401 DO i=1,sNx
402 jG = myYGlobalLo-1+(bj-1)*sNy+j
403 local=225.d0-float((jg-1))/float((ny-1))*37.5d0
404 Solar(i,j,bi,bj) = local
405 ENDDO
406 ENDDO
407 ENDDO
408 ENDDO
409 ENDIF
410 _EXCH_XY_RL(solar, myThid)
411 IF ( TrFile .NE. ' ' ) THEN
412 CALL READ_FLD_XY_RL( TrFile,' ',tr,0,myThid )
413 ELSE
414 DO bj = myByLo(myThid), myByHi(myThid)
415 DO bi = myBxLo(myThid), myBxHi(myThid)
416 DO j=1,sNy
417 DO i=1,sNx
418 jG = myYGlobalLo-1+(bj-1)*sNy+j
419 local=solar(i,j,bi,bj)
420 local=(2.d0*local/stefan)**(0.25d0)-273.16
421 Tr(i,j,bi,bj) = local
422 ENDDO
423 ENDDO
424 ENDDO
425 ENDDO
426 ENDIF
427 _EXCH_XY_RL(Tr, myThid)
428
429 C do specific humidity
430 IF ( QrFile .NE. ' '.AND..NOT. useRelativeHumidity ) THEN
431 CALL READ_FLD_XY_RL( QrFile,' ',qr,0,myThid )
432 ELSEIF ( QrrelFile .NE. ' '.AND.useRelativeHumidity) THEN
433 CALL READ_FLD_XY_RL( QrrelFile,' ',rref,0,myThid )
434 CALL CHEAPAML_CONVERT_HUM(rref, Tr, qr,myThid )
435
436 ELSE
437 C default specific humidity profile to 80% relative humidity
438 DO bj = myByLo(myThid), myByHi(myThid)
439 DO bi = myBxLo(myThid), myBxHi(myThid)
440 DO j=1,sNy
441 DO i=1,sNx
442 c jG = myYGlobalLo-1+(bj-1)*sNy+j
443 local = Tr(i,j,bi,bj)+273.16d0
444 ssqa = ssq0*exp( lath*(ssq1-ssq2/local)) / p0
445 qr(i,j,bi,bj) = 0.8d0*ssqa
446 ENDDO
447 ENDDO
448 ENDDO
449 ENDDO
450 ENDIF
451 _EXCH_XY_RL(qr, myThid)
452 IF ( UWindFile .NE. ' ' ) THEN
453 CALL READ_FLD_XY_RL( UWindFile,' ',uwind,0,myThid )
454 ELSE
455 DO bj = myByLo(myThid), myByHi(myThid)
456 DO bi = myBxLo(myThid), myBxHi(myThid)
457 DO j=1,sNy
458 DO i=1,sNx
459 jG = myYGlobalLo-1+(bj-1)*sNy+j
460 c mod for debug
461 c to return to original code, uncomment following line
462 c comment out 2nd line
463 local=-5.d0*cos(2.d0*pi*float(jg-1)/(float(ny-1)))
464 c local=0.d0*cos(2.d0*pi*float(jg-1)/(float(ny-1)))
465 uwind(i,j,bi,bj) = local
466 ENDDO
467 ENDDO
468 ENDDO
469 ENDDO
470 ENDIF
471 _EXCH_XY_RL(uwind, myThid)
472 IF ( VWindFile .NE. ' ' ) THEN
473 CALL READ_FLD_XY_RL( VWindFile,' ',vwind,0,myThid )
474 ELSE
475 DO bj = myByLo(myThid), myByHi(myThid)
476 DO bi = myBxLo(myThid), myBxHi(myThid)
477 DO j=1,sNy
478 DO i=1,sNx
479 jG = myYGlobalLo-1+(bj-1)*sNy+j
480 vwind(i,j,bi,bj) = 0.d0
481 ENDDO
482 ENDDO
483 ENDDO
484 ENDDO
485 ENDIF
486 _EXCH_XY_RL(vwind, myThid)
487 IF(useStressOption)THEN
488 IF ( UStressFile .NE. ' ' ) THEN
489 CALL READ_FLD_XY_RL( UStressFile,' ',ustress,0,myThid )
490 ELSE
491 write(*,*)' U Stress File absent with stress option'
492 STOP 'ABNORMAL END: S/R CHEAPAML_FIELDS_LOAD'
493 ENDIF
494 IF ( VStressFile .NE. ' ' ) THEN
495 CALL READ_FLD_XY_RL( VStressFile,' ',vstress,0,myThid )
496 ELSE
497 write(*,*)' V Stress File absent with stress option'
498 STOP 'ABNORMAL END: S/R CHEAPAML_FIELDS_LOAD'
499 ENDIF
500 _EXCH_XY_RL(ustress, myThid)
501 _EXCH_XY_RL(vstress, myThid)
502 ENDIF
503 IF (FluxFormula.EQ.'COARE3')THEN
504 IF (WaveHFile.NE.' ')THEN
505 CALL READ_FLD_XY_RL( WaveHFile,' ',wavesh,0,myThid )
506 ENDIF
507 IF (WavePFile.NE.' ')THEN
508 CALL READ_FLD_XY_RL( WavePFile,' ',wavesp,0,myThid )
509 ELSE
510 DO bj = myByLo(myThid), myByHi(myThid)
511 DO bi = myBxLo(myThid), myBxHi(myThid)
512 DO j=1,sNy
513 DO i=1,sNx
514 u=uwind(i,j,bi,bj)**2+vwind(i,j,bi,bj)**2
515 u=dsqrt(u)
516 wavesp(i,j,bi,bj)=0.729 _d 0*u
517 wavesh(i,j,bi,bj)=0.018 _d 0*u*u*(1. _d 0 + .015 _d 0 *u)
518 ENDDO
519 ENDDO
520 ENDDO
521 ENDDO
522 ENDIF
523 _EXCH_XY_RL(wavesp, myThid)
524 _EXCH_XY_RL(wavesh, myThid)
525 ENDIF
526
527 C end if myIter = nIter0
528 ENDIF
529
530 C endif for Steady Option
531 ENDIF
532
533 C fill in outer edges
534 DO bj = myByLo(myThid), myByHi(myThid)
535 DO bi = myBxLo(myThid), myBxHi(myThid)
536 DO j=1-oly,sny+oly
537 jG = myYGlobalLo-1+(bj-1)*sNy+j
538 DO i=1-olx,snx+olx
539 iG=myXGlobalLo-1+(bi-1)*sNx+i
540 if(iG.lt.1)then
541 Tr(i,j,bi,bj)=Tr(1,j,bi,bj)
542 qr(i,j,bi,bj)=qr(1,j,bi,bj)
543 uwind(i,j,bi,bj)=uwind(1,j,bi,bj)
544 vwind(i,j,bi,bj)=vwind(1,j,bi,bj)
545 Solar(i,j,bi,bj)=Solar(1,j,bi,bj)
546 if(UseStressOption)then
547 ustress(i,j,bi,bj)=ustress(1,j,bi,bj)
548 vstress(i,j,bi,bj)=vstress(1,j,bi,bj)
549 endif
550 if(FluxFormula.EQ.'COARE3')then
551 wavesp(i,j,bi,bj)=wavesp(1,j,bi,bj)
552 wavesh(i,j,bi,bj)=wavesh(1,j,bi,bj)
553 endif
554 elseif(iG.gt.Nx)then
555 Tr(i,j,bi,bj)=Tr(sNx,j,bi,bj)
556 qr(i,j,bi,bj)=qr(sNx,j,bi,bj)
557 uwind(i,j,bi,bj)=uwind(sNx,j,bi,bj)
558 vwind(i,j,bi,bj)=vwind(sNx,j,bi,bj)
559 Solar(i,j,bi,bj)=Solar(sNx,j,bi,bj)
560 if(UseStressOption)then
561 ustress(i,j,bi,bj)=ustress(sNx,j,bi,bj)
562 vstress(i,j,bi,bj)=vstress(sNx,j,bi,bj)
563 endif
564 if(FluxFormula.EQ.'COARE3')then
565 wavesp(i,j,bi,bj)=wavesp(sNx,j,bi,bj)
566 wavesh(i,j,bi,bj)=wavesh(sNx,j,bi,bj)
567 endif
568 elseif(jG.lt.1)then
569 Tr(i,j,bi,bj)=Tr(i,1,bi,bj)
570 qr(i,j,bi,bj)=qr(i,1,bi,bj)
571 uwind(i,j,bi,bj)=uwind(i,1,bi,bj)
572 vwind(i,j,bi,bj)=vwind(i,1,bi,bj)
573 Solar(i,j,bi,bj)=Solar(i,1,bi,bj)
574 if(UseStressOption)then
575 ustress(i,j,bi,bj)=ustress(i,1,bi,bj)
576 vstress(i,j,bi,bj)=vstress(i,1,bi,bj)
577 endif
578 if(FluxFormula.EQ.'COARE3')then
579 wavesp(i,j,bi,bj)=wavesp(i,1,bi,bj)
580 wavesh(i,j,bi,bj)=wavesh(i,1,bi,bj)
581 endif
582 elseif(jG.gt.sNy)then
583 Tr(i,j,bi,bj)=Tr(i,sNy,bi,bj)
584 qr(i,j,bi,bj)=qr(i,sNy,bi,bj)
585 uwind(i,j,bi,bj)=uwind(i,sNy,bi,bj)
586 vwind(i,j,bi,bj)=vwind(i,sNy,bi,bj)
587 Solar(i,j,bi,bj)=Solar(i,sNy,bi,bj)
588 if(UseStressOption)then
589 ustress(i,j,bi,bj)=ustress(i,sNy,bi,bj)
590 vstress(i,j,bi,bj)=vstress(i,sNy,bi,bj)
591 endif
592 if(FluxFormula.EQ.'COARE3')then
593 wavesp(i,j,bi,bj)=wavesp(i,sNy,bi,bj)
594 wavesh(i,j,bi,bj)=wavesh(i,sNy,bi,bj)
595 endif
596 endif
597 ENDDO
598 ENDDO
599 ENDDO
600 ENDDO
601
602 RETURN
603 END

  ViewVC Help
Powered by ViewVC 1.1.22