/[MITgcm]/MITgcm_contrib/sciascia/rbcs/rbcs_fields_load.F
ViewVC logotype

Annotation of /MITgcm_contrib/sciascia/rbcs/rbcs_fields_load.F

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


Revision 1.1 - (hide annotations) (download)
Wed Aug 8 01:57:14 2012 UTC (12 years, 11 months ago) by heimbach
Branch: MAIN
CVS Tags: HEAD
Add a modified version of pkg/rbcs that allows several rbcs
fields to be read with independent frequencies.
The idea is for each i = 1 , ... , U/V/WnLEN
one can define a separate mask and relaxation file
and separate/independent periods.

1 heimbach 1.1 C $Header: /u/gcmpack/MITgcm/pkg/rbcs/rbcs_fields_load.F,v 1.15 2011/06/07 22:25:10 jmc Exp $
2     C $Name: $
3    
4     #include "RBCS_OPTIONS.h"
5    
6     C !ROUTINE: RBCS_FIELDS_LOAD
7     C !INTERFACE:
8     SUBROUTINE RBCS_FIELDS_LOAD( myTime, myIter, myThid )
9    
10     C !DESCRIPTION: \bv
11     C *==========================================================*
12     C | SUBROUTINE RBCS_FIELDS_LOAD
13     C | o Control reading of fields from external source.
14     C *==========================================================*
15     C | RBCS External source field loading routine.
16     C | This routine is called every time we want to
17     C | load a a set of external fields. The routine decides
18     C | which fields to load and then reads them in.
19     C *==========================================================*
20     C \ev
21    
22     C !USES:
23     IMPLICIT NONE
24     C === Global variables ===
25     #include "SIZE.h"
26     #include "EEPARAMS.h"
27     #include "PARAMS.h"
28     #ifdef ALLOW_PTRACERS
29     #include "PTRACERS_SIZE.h"
30     #include "PTRACERS_PARAMS.h"
31     #endif
32     #include "RBCS_SIZE.h"
33     #include "RBCS_PARAMS.h"
34     #include "RBCS_FIELDS.h"
35    
36     C !INPUT/OUTPUT PARAMETERS:
37     C === Routine arguments ===
38     C myTime :: Simulation time
39     C myIter :: Simulation timestep number
40     C myThid :: Thread no. that called this routine.
41     _RL myTime
42     INTEGER myIter
43     INTEGER myThid
44    
45     C !FUNCTIONS:
46     INTEGER IFNBLNK, ILNBLNK
47     EXTERNAL IFNBLNK, ILNBLNK
48    
49     C !LOCAL VARIABLES:
50     C === Local arrays ===
51     C [01] :: End points for interpolation
52     C Above use static heap storage to allow exchange.
53     C aWght, bWght :: Interpolation weights
54    
55     INTEGER bi, bj, i, j, k
56     INTEGER ium,ivm,iwm
57     INTEGER intimeP, intime0, intime1
58     _RL aWght, bWght, locTime
59     INTEGER intimeUP(UmLEN), intimeU0(UmLEN), intimeU1(UmLEN)
60     _RL UaWght(UmLEN), UbWght(UmLEN), UlocTime(UmLEN)
61     INTEGER intimeVP(VmLEN), intimeV0(VmLEN), intimeV1(VmLEN)
62     _RL VaWght(VmLEN), VbWght(VmLEN), VlocTime(VmLEN)
63     INTEGER intimeWP(WmLEN), intimeW0(WmLEN), intimeW1(WmLEN)
64     _RL WaWght(WmLEN), WbWght(WmLEN), WlocTime(WmLEN)
65     INTEGER Ifprd
66     #ifdef ALLOW_PTRACERS
67     INTEGER iTracer
68     #endif
69     INTEGER IL, initer0, initer1
70     INTEGER initerU0(UmLEN), initerU1(UmLEN)
71     INTEGER initerV0(VmLEN), initerV1(VmLEN)
72     INTEGER initerW0(WmLEN), initerW1(WmLEN)
73     CHARACTER*(MAX_LEN_FNAM) fullName
74     CEOP
75    
76     #ifdef ALLOW_RBCS
77     CALL TIMER_START('RBCS_FIELDS_LOAD [I/O]', myThid)
78    
79     C-- First call requires that we initialize everything to zero for safety
80     C <= already done in RBCS_INIT_VARIA
81    
82     C-- Now calculate whether it is time to update the forcing arrays
83     bi = myBxLo(myThid)
84     bj = myByLo(myThid)
85     IF (rbcsForcingPeriod.GT.0. _d 0) THEN
86     locTime = myTime - rbcsForcingOffset
87     CALL GET_PERIODIC_INTERVAL(
88     O intimeP, intime0, intime1, bWght, aWght,
89     I rbcsForcingCycle, rbcsForcingPeriod,
90     I deltaTclock, locTime, myThid )
91     #ifdef ALLOW_DEBUG
92     IF ( debugLevel.GE.debLevB ) THEN
93     _BEGIN_MASTER(myThid)
94     WRITE(standardMessageUnit,'(A,I10,A,4I5,A,2F14.10)')
95     & ' RBCS_FIELDS_LOAD,', myIter,
96     & ' : iP,iLd,i0,i1=', intimeP,rbcsLdRec(bi,bj), intime0,intime1,
97     & ' ; Wght=', bWght, aWght
98     _END_MASTER(myThid)
99     ENDIF
100     #endif /* ALLOW_DEBUG */
101     ELSE
102     intimeP = 1
103     intime1 = 1
104     intime0 = 1
105     aWght = .5 _d 0
106     bWght = .5 _d 0
107     ENDIF
108    
109     #ifdef ALLOW_AUTODIFF_TAMC
110     C- assuming that we call S/R RBCS_FIELDS_LOAD at each time-step and
111     C with increasing time, this will catch when we need to load new records;
112     C But with Adjoint run, this is not always the case => might end-up using
113     C the wrong time-records
114     IF ( intime0.NE.intimeP .OR. myIter.EQ.nIter0 ) THEN
115     #else /* ALLOW_AUTODIFF_TAMC */
116     C- Make no assumption on sequence of calls to RBCS_FIELDS_LOAD ;
117     C This is the correct formulation (works in Adjoint run).
118     C Unfortunatly, produces many recomputations <== not used until it is fixed
119     IF ( intime1.NE.rbcsLdRec(bi,bj) ) THEN
120     #endif /* ALLOW_AUTODIFF_TAMC */
121    
122     C-- If the above condition is met then we need to read in
123     C data for the period ahead and the period behind myTime.
124     IF ( debugLevel.GE.debLevZero ) THEN
125     _BEGIN_MASTER(myThid)
126     WRITE(standardMessageUnit,'(A,I10,A,2(2I5,A))')
127     & ' RBCS_FIELDS_LOAD, it=', myIter,
128     & ' : Reading new data, i0,i1=', intime0, intime1,
129     & ' (prev=', intimeP, rbcsLdRec(bi,bj), ' )'
130     _END_MASTER(myThid)
131     ENDIF
132    
133     C for rbcsSingleTimeFiles=.TRUE.
134     Ifprd = NINT(rbcsForcingPeriod/deltaTrbcs)
135     initer0 = rbcsIter0 + intime0*Ifprd
136     initer1 = rbcsIter0 + intime1*Ifprd
137    
138     IF ( useRBCtemp .AND. relaxTFile .NE. ' ' ) THEN
139     IF ( rbcsSingleTimeFiles ) THEN
140     IL=ILNBLNK( relaxTFile )
141     WRITE(fullName,'(2a,i10.10)') relaxTFile(1:IL),'.',initer0
142     CALL READ_REC_XYZ_RS(fullName, rbct0, 1, myIter, myThid)
143     WRITE(fullName,'(2a,i10.10)') relaxTFile(1:IL),'.',initer1
144     CALL READ_REC_XYZ_RS(fullName, rbct1, 1, myIter, myThid)
145     ELSE
146     CALL READ_REC_XYZ_RS(relaxTFile,rbct0,intime0,myIter,myThid)
147     CALL READ_REC_XYZ_RS(relaxTFile,rbct1,intime1,myIter,myThid)
148     ENDIF
149     CALL EXCH_XYZ_RS( rbct0 , myThid )
150     CALL EXCH_XYZ_RS( rbct1 , myThid )
151     ENDIF
152     IF ( useRBCsalt .AND. relaxSFile .NE. ' ' ) THEN
153     IF ( rbcsSingleTimeFiles ) THEN
154     IL=ILNBLNK( relaxSFile )
155     WRITE(fullName,'(2a,i10.10)') relaxSFile(1:IL),'.',initer0
156     CALL READ_REC_XYZ_RS(fullName, rbcs0, 1, myIter, myThid)
157     WRITE(fullName,'(2a,i10.10)') relaxSFile(1:IL),'.',initer1
158     CALL READ_REC_XYZ_RS(fullName, rbcs1, 1, myIter, myThid)
159     ELSE
160     CALL READ_REC_XYZ_RS(relaxSFile,rbcs0,intime0,myIter,myThid)
161     CALL READ_REC_XYZ_RS(relaxSFile,rbcs1,intime1,myIter,myThid)
162     ENDIF
163     CALL EXCH_XYZ_RS( rbcs0 , myThid )
164     CALL EXCH_XYZ_RS( rbcs1 , myThid )
165     ENDIF
166    
167     #ifdef ALLOW_PTRACERS
168     IF ( usePTRACERS ) THEN
169     DO iTracer = 1, PTRACERS_numInUse
170     IF ( useRBCptrnum(iTracer) .AND.
171     & relaxPtracerFile(iTracer).NE. ' ' ) THEN
172     IF ( rbcsSingleTimeFiles ) THEN
173     IL=ILNBLNK( relaxPtracerFile(iTracer) )
174     WRITE(fullName,'(2a,i10.10)') relaxPtracerFile(iTracer)(1:IL)
175     & ,'.',initer0
176     CALL READ_REC_XYZ_RS( fullName,
177     & rbcptr0(1-Olx,1-Oly,1,1,1,iTracer),
178     & 1, myIter, myThid )
179     WRITE(fullName,'(2a,i10.10)') relaxPtracerFile(iTracer)(1:IL)
180     & ,'.',initer1
181     CALL READ_REC_XYZ_RS( fullName,
182     & rbcptr1(1-Olx,1-Oly,1,1,1,iTracer),
183     & 1, myIter, myThid )
184     ELSE
185     CALL READ_REC_XYZ_RS( relaxPtracerFile(iTracer),
186     & rbcptr0(1-Olx,1-Oly,1,1,1,iTracer),
187     & intime0, myIter, myThid )
188     CALL READ_REC_XYZ_RS( relaxPtracerFile(iTracer),
189     & rbcptr1(1-Olx,1-Oly,1,1,1,iTracer),
190     & intime1, myIter, myThid )
191     ENDIF
192     CALL EXCH_XYZ_RS( rbcptr0(1-Olx,1-Oly,1,1,1,iTracer),myThid )
193     CALL EXCH_XYZ_RS( rbcptr1(1-Olx,1-Oly,1,1,1,iTracer),myThid )
194     ENDIF
195     ENDDO
196     ENDIF
197     #endif /* ALLOW_PTRACERS */
198    
199     C- save newly loaded time-record
200     DO bj = myByLo(myThid), myByHi(myThid)
201     DO bi = myBxLo(myThid), myBxHi(myThid)
202     rbcsLdRec(bi,bj) = intime1
203     ENDDO
204     ENDDO
205     C-- end if-block for loading new time-records
206     ENDIF
207     #ifndef DISABLE_RBCS_MOM
208     DO ium=1,UmLEN
209     IF (rbcsForcingUPeriod(ium).GT.0. _d 0) THEN
210     UlocTime(ium) = myTime - rbcsForcingUOffset(ium)
211     CALL GET_PERIODIC_INTERVAL(
212     O intimeUP(ium), intimeU0(ium), intimeU1(ium),
213     I UbWght(ium), UaWght(ium),
214     I rbcsForcingUCycle(ium), rbcsForcingUPeriod(ium),
215     I deltaTclock, UlocTime(ium), myThid )
216     #ifdef ALLOW_DEBUG
217     IF ( debugLevel.GE.debLevB ) THEN
218     _BEGIN_MASTER(myThid)
219     WRITE(standardMessageUnit,'(A,I10,A,4I5,A,2F14.10)')
220     & ' RBCS_FIELDS_LOAD,', myIter,
221     & ' : iP,iLd,i0,i1=', intimeUP(ium),rbcsLdRec(bi,bj),
222     & intimeU0(ium),intimeU1(ium),
223     & ' ; Wght=', UbWght(ium), UaWght(ium)
224     _END_MASTER(myThid)
225     ENDIF
226     #endif /* ALLOW_DEBUG */
227     ELSE
228     intimeUP(ium) = 1
229     intimeU1(ium) = 1
230     intimeU0(ium) = 1
231     UaWght(ium) = .5 _d 0
232     UbWght(ium) = .5 _d 0
233     ENDIF
234    
235     #ifdef ALLOW_AUTODIFF_TAMC
236     C- assuming that we call S/R RBCS_FIELDS_LOAD at each time-step and
237     C with increasing time, this will catch when we need to load new records;
238     C But with Adjoint run, this is not always the case => might end-up using
239     C the wrong time-records
240     IF ( intimeU0(ium).NE.intimeUP(ium) .OR. myIter.EQ.nIter0 ) THEN
241     #else /* ALLOW_AUTODIFF_TAMC */
242     C- Make no assumption on sequence of calls to RBCS_FIELDS_LOAD ;
243     C This is the correct formulation (works in Adjoint run).
244     C Unfortunatly, produces many recomputations <== not used until it is fixed
245     IF ( intimeU1(ium).NE.rbcsLdRec(bi,bj) ) THEN
246     #endif /* ALLOW_AUTODIFF_TAMC */
247    
248     C-- If the above condition is met then we need to read in
249     C data for the period ahead and the period behind myTime.
250     IF ( debugLevel.GE.debLevZero ) THEN
251     _BEGIN_MASTER(myThid)
252     WRITE(standardMessageUnit,'(A,I10,A,2(2I5,A))')
253     & ' RBCS_FIELDS_LOAD, it=', myIter,
254     & ' : Reading new data, i0,i1=', intimeU0(ium), intimeU1(ium),
255     & ' (prev=', intimeUP(ium), rbcsLdRec(bi,bj), ' )'
256     _END_MASTER(myThid)
257     ENDIF
258    
259     C for rbcsSingleTimeFiles=.TRUE.
260     Ifprd = NINT(rbcsForcingUPeriod(ium)/deltaTrbcs)
261     initerU0(ium) = rbcsIter0 + intimeU0(ium)*Ifprd
262     initerU1(ium) = rbcsIter0 + intimeU1(ium)*Ifprd
263    
264     IF ( useRBCuVel(ium) .AND. relaxUFile(ium).NE.' ' ) THEN
265     IF ( rbcsSingleTimeFiles ) THEN
266     IL=ILNBLNK( relaxUFile(ium) )
267     WRITE(fullName,'(2A,I10.10)') relaxUFile(1:IL),'.',initer0
268     CALL READ_REC_XYZ_RS(fullName, rbcu0, 1, myIter, myThid)
269     WRITE(fullName,'(2A,I10.10)') relaxUFile(1:IL),'.',initer1
270     CALL READ_REC_XYZ_RS(fullName, rbcu1, 1, myIter, myThid)
271     ELSE
272     CALL READ_REC_XYZ_RS(relaxUFile(ium),rbcu0,
273     & intime0,myIter,myThid)
274    
275     CALL READ_REC_XYZ_RS(relaxUFile(ium),rbcu1,
276     & intime0,myIter,myThid)
277     ENDIF
278     ENDIF
279    
280     C- save newly loaded time-record
281     DO bj = myByLo(myThid), myByHi(myThid)
282     DO bi = myBxLo(myThid), myBxHi(myThid)
283     UrbcsLdRec(bi,bj) = intimeU1(ium)
284     ENDDO
285     ENDDO
286     C-- end if-block for loading new time-records
287     ENDIF
288     ENDDO
289    
290     DO ivm=1,VmLEN
291     IF (rbcsForcingVPeriod(ivm).GT.0. _d 0) THEN
292     VlocTime(ivm) = myTime - rbcsForcingVOffset(ivm)
293     CALL GET_PERIODIC_INTERVAL(
294     O intimeVP(ivm), intimeV0(ivm), intimeV1(ivm),
295     I VbWght(ivm), VaWght(ivm),
296     I rbcsForcingVCycle(ivm), rbcsForcingVPeriod(ivm),
297     I deltaTclock, VlocTime(ivm), myThid )
298     #ifdef ALLOW_DEBUG
299     IF ( debugLevel.GE.debLevB ) THEN
300     _BEGIN_MASTER(myThid)
301     WRITE(standardMessageUnit,'(A,I10,A,4I5,A,2F14.10)')
302     & ' RBCS_FIELDS_LOAD,', myIter,
303     & ' : iP,iLd,i0,i1=', intimeVP(ivm),rbcsLdRec(bi,bj),
304     & intimeV0(ivm),intimeV1(ivm),
305     & ' ; Wght=', VbWght(ivm), VaWght(ivm)
306     _END_MASTER(myThid)
307     ENDIF
308     #endif /* ALLOW_DEBUG */
309     ELSE
310     intimeVP(ivm) = 1
311     intimeV1(ivm) = 1
312     intimeV0(ivm) = 1
313     VaWght(ivm) = .5 _d 0
314     VbWght(ivm) = .5 _d 0
315     ENDIF
316    
317     #ifdef ALLOW_AUTODIFF_TAMC
318     C- assuming that we call S/R RBCS_FIELDS_LOAD at each time-step and
319     C with increasing time, this will catch when we need to load new records;
320     C But with Adjoint run, this is not always the case => might end-up using
321     C the wrong time-records
322     IF ( intimeV0(ivm).NE.intimeVP(ivm) .OR. myIter.EQ.nIter0 ) THEN
323     #else /* ALLOW_AUTODIFF_TAMC */
324     C- Make no assumption on sequence of calls to RBCS_FIELDS_LOAD ;
325     C This is the correct formulation (works in Adjoint run).
326     C Unfortunatly, produces many recomputations <== not used until it is fixed
327     IF ( intimeV1(ivm).NE.rbcsLdRec(bi,bj) ) THEN
328     #endif /* ALLOW_AUTODIFF_TAMC */
329    
330     C-- If the above condition is met then we need to read in
331     C data for the period ahead and the period behind myTime.
332     IF ( debugLevel.GE.debLevZero ) THEN
333     _BEGIN_MASTER(myThid)
334     WRITE(standardMessageUnit,'(A,I10,A,2(2I5,A))')
335     & ' RBCS_FIELDS_LOAD, it=', myIter,
336     & ' : Reading new data, i0,i1=', intimeV0(ivm), intimeV1(ivm),
337     & ' (prev=', intimeVP(ivm), rbcsLdRec(bi,bj), ' )'
338     _END_MASTER(myThid)
339     ENDIF
340    
341     C for rbcsSingleTimeFiles=.TRUE.
342     Ifprd = NINT(rbcsForcingVPeriod(ivm)/deltaTrbcs)
343     initerV0(ivm) = rbcsIter0 + intimeV0(ivm)*Ifprd
344     initerV1(ivm) = rbcsIter0 + intimeV1(ivm)*Ifprd
345    
346     IF ( useRBCvVel(ivm) .AND. relaxVFile(ivm).NE.' ' ) THEN
347     IF ( rbcsSingleTimeFiles ) THEN
348     IL=ILNBLNK( relaxVFile(ivm) )
349     WRITE(fullName,'(2A,I10.10)') relaxVFile(1:IL),'.',initer0
350     CALL READ_REC_XYZ_RS(fullName, rbcv0, 1, myIter, myThid)
351     WRITE(fullName,'(2A,I10.10)') relaxVFile(1:IL),'.',initer1
352     CALL READ_REC_XYZ_RS(fullName, rbcv1, 1, myIter, myThid)
353     ELSE
354     CALL READ_REC_XYZ_RS(relaxVFile(ivm),rbcv0,
355     & intime0,myIter,myThid)
356    
357     CALL READ_REC_XYZ_RS(relaxVFile(ivm),rbcv1,
358     & intime0,myIter,myThid)
359     ENDIF
360     ENDIF
361     C- save newly loaded time-record
362     DO bj = myByLo(myThid), myByHi(myThid)
363     DO bi = myBxLo(myThid), myBxHi(myThid)
364     VrbcsLdRec(bi,bj) = intimeV1(ivm)
365     ENDDO
366     ENDDO
367     C-- end if-block for loading new time-records
368     ENDIF
369     ENDDO
370     #ifdef ALLOW_NONHYDROSTATIC
371     DO iwm=1, WmLEN
372     IF (rbcsForcingWPeriod(iwm).GT.0. _d 0) THEN
373     WlocTime(iwm) = myTime - rbcsForcingWOffset(iwm)
374     CALL GET_PERIODIC_INTERVAL(
375     O intimeWP(iwm), intimeW0(iwm), intimeW1(iwm),
376     I WbWght(iwm), WaWght(iwm),
377     I rbcsForcingWCycle(iwm), rbcsForcingWPeriod(iwm),
378     I deltaTclock, WlocTime(iwm), myThid )
379     #ifdef ALLOW_DEBUG
380     IF ( debugLevel.GE.debLevB ) THEN
381     _BEGIN_MASTER(myThid)
382     WRITE(standardMessageUnit,'(A,I10,A,4I5,A,2F14.10)')
383     & ' RBCS_FIELDS_LOAD,', myIter,
384     & ' : iP,iLd,i0,i1=', intimeWP(iwm),rbcsLdRec(bi,bj),
385     & intimeW0(iwm),intimeW1(iwm),
386     & ' ; Wght=', WbWght(iwm), WaWght(iwm)
387     _END_MASTER(myThid)
388     ENDIF
389     #endif /* ALLOW_DEBUG */
390     ELSE
391     intimeWP(iwm) = 1
392     intimeW1(iwm) = 1
393     intimeW0(iwm) = 1
394     WaWght(iwm) = .5 _d 0
395     WbWght(iwm) = .5 _d 0
396     ENDIF
397    
398     #ifdef ALLOW_AUTODIFF_TAMC
399     C- assuming that we call S/R RBCS_FIELDS_LOAD at each time-step and
400     C with increasing time, this will catch when we need to load new records;
401     C But with Adjoint run, this is not always the case => might end-up using
402     C the wrong time-records
403     IF ( intimeW0(iwm).NE.intimeWP(iwm) .OR. myIter.EQ.nIter0 ) THEN
404     #else /* ALLOW_AUTODIFF_TAMC */
405     C- Make no assumption on sequence of calls to RBCS_FIELDS_LOAD ;
406     C This is the correct formulation (works in Adjoint run).
407     C Unfortunatly, produces many recomputations <== not used until it is fixed
408     IF ( intimeW1(iwm).NE.rbcsLdRec(bi,bj) ) THEN
409     #endif /* ALLOW_AUTODIFF_TAMC */
410    
411     C-- If the above condition is met then we need to read in
412     C data for the period ahead and the period behind myTime.
413     IF ( debugLevel.GE.debLevZero ) THEN
414     _BEGIN_MASTER(myThid)
415     WRITE(standardMessageUnit,'(A,I10,A,2(2I5,A))')
416     & ' RBCS_FIELDS_LOAD, it=', myIter,
417     & ' : Reading new data, i0,i1=', intimeW0(iwm), intimeW1(iwm),
418     & ' (prev=', intimeWP(iwm), rbcsLdRec(bi,bj), ' )'
419     _END_MASTER(myThid)
420     ENDIF
421    
422     C for rbcsSingleTimeFiles=.TRUE.
423     Ifprd = NINT(rbcsForcingWPeriod(iwm)/deltaTrbcs)
424     initerW0(iwm) = rbcsIter0 + intimeW0(iwm)*Ifprd
425     initerW1(iwm) = rbcsIter0 + intimeW1(iwm)*Ifprd
426     IF ( useRBCwVel(iwm) .AND. relaxWFile(iwm).NE.' ' ) THEN
427     IF ( rbcsSingleTimeFiles ) THEN
428     IL=ILNBLNK( relaxWFile(iwm) )
429     WRITE(fullName,'(2A,I10.10)') relaxWFile(1:IL),'.',initer0
430     CALL READ_REC_XYZ_RS(fullName, rbcw0, 1
431     & , myIter, myThid)
432     WRITE(fullName,'(2A,I10.10)') relaxWFile(1:IL),'.',initer1
433     CALL READ_REC_XYZ_RS(fullName, rbcw1, 1
434     & , myIter, myThid)
435     ELSE
436     CALL READ_REC_XYZ_RS(relaxWFile(iwm),rbcw0,
437     & intime0,myIter,myThid)
438    
439     CALL READ_REC_XYZ_RS(relaxWFile(iwm),rbcw1,
440     & intime0,myIter,myThid)
441     ENDIF
442     ENDIF
443     C- save newly loaded time-record
444     DO bj = myByLo(myThid), myByHi(myThid)
445     DO bi = myBxLo(myThid), myBxHi(myThid)
446     WrbcsLdRec(bi,bj) = intimeW1(iwm)
447     ENDDO
448     ENDDO
449     C-- end if-block for loading new time-records
450     ENDIF
451     ENDDO
452     #endif
453     C IF ( (useRBCuVel .AND. relaxUFile.NE.' ') .OR.
454     C & (useRBCvVel .AND. relaxVFile.NE.' ') ) THEN
455     C CALL EXCH_UV_XYZ_RS( rbcu0, rbcv0, .TRUE., myThid )
456     C CALL EXCH_UV_XYZ_RS( rbcu1, rbcv1, .TRUE., myThid )
457     C ENDIF
458     #endif /* DISABLE_RBCS_MOM */
459    
460    
461    
462     C-- Interpolate
463     DO bj = myByLo(myThid), myByHi(myThid)
464     DO bi = myBxLo(myThid), myBxHi(myThid)
465     #ifndef DISABLE_RBCS_MOM
466     DO ium=1,UmLEN
467     IF ( useRBCuVel(ium)) THEN
468     DO k=1,Nr
469     DO j=1-Oly,sNy+Oly
470     DO i=1-Olx,sNx+Olx
471     RBCuVel(i,j,k,bi,bj,ium) = UbWght(ium)
472     & *rbcu0(i,j,k,bi,bj,ium)
473     & +UaWght(ium)*rbcu1(i,j,k,bi,bj,ium)
474     ENDDO
475     ENDDO
476     ENDDO
477     ENDIF
478     ENDDO
479     DO ivm=1,VmLEN
480     IF ( useRBCvVel(ivm)) THEN
481     DO k=1,Nr
482     DO j=1-Oly,sNy+Oly
483     DO i=1-Olx,sNx+Olx
484     RBCvVel(i,j,k,bi,bj,ivm) = VbWght(ivm)
485     & *rbcv0(i,j,k,bi,bj,ivm)
486     & +VaWght(ivm)*rbcv1(i,j,k,bi,bj,ivm)
487     ENDDO
488     ENDDO
489     ENDDO
490     ENDIF
491     ENDDO
492     DO iwm=1,WmLEN
493     IF ( useRBCwVel(iwm)) THEN
494     DO k=1,Nr
495     DO j=1-Oly,sNy+Oly
496     DO i=1-Olx,sNx+Olx
497     RBCwVel(i,j,k,bi,bj,iwm) = WbWght(iwm)
498     & *rbcw0(i,j,k,bi,bj,iwm)
499     & +WaWght(iwm)*rbcw1(i,j,k,bi,bj,iwm)
500     ENDDO
501     ENDDO
502     ENDDO
503     ENDIF
504     ENDDO
505     #endif /* DISABLE_RBCS_MOM */
506     DO k=1,Nr
507     DO j=1-Oly,sNy+Oly
508     DO i=1-Olx,sNx+Olx
509     RBCtemp(i,j,k,bi,bj) = bWght*rbct0(i,j,k,bi,bj)
510     & +aWght*rbct1(i,j,k,bi,bj)
511     RBCsalt(i,j,k,bi,bj) = bWght*rbcs0(i,j,k,bi,bj)
512     & +aWght*rbcs1(i,j,k,bi,bj)
513     ENDDO
514     ENDDO
515     ENDDO
516     ENDDO
517     ENDDO
518    
519     #ifdef ALLOW_PTRACERS
520     IF ( usePTRACERS ) THEN
521     DO iTracer = 1, PTRACERS_numInUse
522     IF (useRBCptrnum(iTracer)) THEN
523     DO bj = myByLo(myThid), myByHi(myThid)
524     DO bi = myBxLo(myThid), myBxHi(myThid)
525     DO k=1,Nr
526     DO j=1-Oly,sNy+Oly
527     DO i=1-Olx,sNx+Olx
528     RBC_ptracers(i,j,k,bi,bj,iTracer) =
529     & bWght*rbcptr0(i,j,k,bi,bj,iTracer)
530     & +aWght*rbcptr1(i,j,k,bi,bj,iTracer)
531     ENDDO
532     ENDDO
533     ENDDO
534     ENDDO
535     ENDDO
536     ENDIF
537     ENDDO
538     ENDIF
539     #endif /* ALLOW_PTRACERS */
540    
541     CALL TIMER_STOP ('RBCS_FIELDS_LOAD [I/O]', myThid)
542    
543     #endif /* ALLOW_RBCS */
544    
545     RETURN
546     END

  ViewVC Help
Powered by ViewVC 1.1.22