/[MITgcm]/MITgcm/pkg/rbcs/rbcs_fields_load.F
ViewVC logotype

Contents of /MITgcm/pkg/rbcs/rbcs_fields_load.F

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


Revision 1.15 - (show annotations) (download)
Tue Jun 7 22:25:10 2011 UTC (12 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint64, checkpoint65, checkpoint63, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint62z, HEAD
Changes since 1.14: +9 -7 lines
refine debugLevel criteria when printing messages

1 C $Header: /u/gcmpack/MITgcm/pkg/rbcs/rbcs_fields_load.F,v 1.14 2011/05/14 19:52:12 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 intimeP, intime0, intime1
57 _RL aWght, bWght, locTime
58 INTEGER Ifprd
59 #ifdef ALLOW_PTRACERS
60 INTEGER iTracer
61 #endif
62 INTEGER IL, initer0, initer1
63 CHARACTER*(MAX_LEN_FNAM) fullName
64 CEOP
65
66 #ifdef ALLOW_RBCS
67 CALL TIMER_START('RBCS_FIELDS_LOAD [I/O]', myThid)
68
69 C-- First call requires that we initialize everything to zero for safety
70 C <= already done in RBCS_INIT_VARIA
71
72 C-- Now calculate whether it is time to update the forcing arrays
73 bi = myBxLo(myThid)
74 bj = myByLo(myThid)
75 IF (rbcsForcingPeriod.GT.0. _d 0) THEN
76 locTime = myTime - rbcsForcingOffset
77 CALL GET_PERIODIC_INTERVAL(
78 O intimeP, intime0, intime1, bWght, aWght,
79 I rbcsForcingCycle, rbcsForcingPeriod,
80 I deltaTclock, locTime, myThid )
81 #ifdef ALLOW_DEBUG
82 IF ( debugLevel.GE.debLevB ) THEN
83 _BEGIN_MASTER(myThid)
84 WRITE(standardMessageUnit,'(A,I10,A,4I5,A,2F14.10)')
85 & ' RBCS_FIELDS_LOAD,', myIter,
86 & ' : iP,iLd,i0,i1=', intimeP,rbcsLdRec(bi,bj), intime0,intime1,
87 & ' ; Wght=', bWght, aWght
88 _END_MASTER(myThid)
89 ENDIF
90 #endif /* ALLOW_DEBUG */
91 ELSE
92 intimeP = 1
93 intime1 = 1
94 intime0 = 1
95 aWght = .5 _d 0
96 bWght = .5 _d 0
97 ENDIF
98
99 #ifdef ALLOW_AUTODIFF_TAMC
100 C- assuming that we call S/R RBCS_FIELDS_LOAD at each time-step and
101 C with increasing time, this will catch when we need to load new records;
102 C But with Adjoint run, this is not always the case => might end-up using
103 C the wrong time-records
104 IF ( intime0.NE.intimeP .OR. myIter.EQ.nIter0 ) THEN
105 #else /* ALLOW_AUTODIFF_TAMC */
106 C- Make no assumption on sequence of calls to RBCS_FIELDS_LOAD ;
107 C This is the correct formulation (works in Adjoint run).
108 C Unfortunatly, produces many recomputations <== not used until it is fixed
109 IF ( intime1.NE.rbcsLdRec(bi,bj) ) THEN
110 #endif /* ALLOW_AUTODIFF_TAMC */
111
112 C-- If the above condition is met then we need to read in
113 C data for the period ahead and the period behind myTime.
114 IF ( debugLevel.GE.debLevZero ) THEN
115 _BEGIN_MASTER(myThid)
116 WRITE(standardMessageUnit,'(A,I10,A,2(2I5,A))')
117 & ' RBCS_FIELDS_LOAD, it=', myIter,
118 & ' : Reading new data, i0,i1=', intime0, intime1,
119 & ' (prev=', intimeP, rbcsLdRec(bi,bj), ' )'
120 _END_MASTER(myThid)
121 ENDIF
122
123 C for rbcsSingleTimeFiles=.TRUE.
124 Ifprd = NINT(rbcsForcingPeriod/deltaTrbcs)
125 initer0 = rbcsIter0 + intime0*Ifprd
126 initer1 = rbcsIter0 + intime1*Ifprd
127
128 #ifndef DISABLE_RBCS_MOM
129 IF ( useRBCuVel .AND. relaxUFile.NE.' ' ) THEN
130 IF ( rbcsSingleTimeFiles ) THEN
131 IL=ILNBLNK( relaxUFile )
132 WRITE(fullName,'(2A,I10.10)') relaxUFile(1:IL),'.',initer0
133 CALL READ_REC_XYZ_RS(fullName, rbcu0, 1, myIter, myThid)
134 WRITE(fullName,'(2A,I10.10)') relaxUFile(1:IL),'.',initer1
135 CALL READ_REC_XYZ_RS(fullName, rbcu1, 1, myIter, myThid)
136 ELSE
137 CALL READ_REC_XYZ_RS(relaxUFile,rbcu0,intime0,myIter,myThid)
138 CALL READ_REC_XYZ_RS(relaxUFile,rbcu1,intime1,myIter,myThid)
139 ENDIF
140 ENDIF
141 IF ( useRBCvVel .AND. relaxVFile.NE.' ' ) THEN
142 IF ( rbcsSingleTimeFiles ) THEN
143 IL=ILNBLNK( relaxVFile )
144 WRITE(fullName,'(2A,I10.10)') relaxVFile(1:IL),'.',initer0
145 CALL READ_REC_XYZ_RS(fullName, rbcv0, 1, myIter, myThid)
146 WRITE(fullName,'(2A,I10.10)') relaxVFile(1:IL),'.',initer1
147 CALL READ_REC_XYZ_RS(fullName, rbcv1, 1, myIter, myThid)
148 ELSE
149 CALL READ_REC_XYZ_RS(relaxVFile,rbcv0,intime0,myIter,myThid)
150 CALL READ_REC_XYZ_RS(relaxVFile,rbcv1,intime1,myIter,myThid)
151 ENDIF
152 ENDIF
153 IF ( (useRBCuVel .AND. relaxUFile.NE.' ') .OR.
154 & (useRBCvVel .AND. relaxVFile.NE.' ') ) THEN
155 CALL EXCH_UV_XYZ_RS( rbcu0, rbcv0, .TRUE., myThid )
156 CALL EXCH_UV_XYZ_RS( rbcu1, rbcv1, .TRUE., myThid )
157 ENDIF
158 #endif /* DISABLE_RBCS_MOM */
159 IF ( useRBCtemp .AND. relaxTFile .NE. ' ' ) THEN
160 IF ( rbcsSingleTimeFiles ) THEN
161 IL=ILNBLNK( relaxTFile )
162 WRITE(fullName,'(2a,i10.10)') relaxTFile(1:IL),'.',initer0
163 CALL READ_REC_XYZ_RS(fullName, rbct0, 1, myIter, myThid)
164 WRITE(fullName,'(2a,i10.10)') relaxTFile(1:IL),'.',initer1
165 CALL READ_REC_XYZ_RS(fullName, rbct1, 1, myIter, myThid)
166 ELSE
167 CALL READ_REC_XYZ_RS(relaxTFile,rbct0,intime0,myIter,myThid)
168 CALL READ_REC_XYZ_RS(relaxTFile,rbct1,intime1,myIter,myThid)
169 ENDIF
170 CALL EXCH_XYZ_RS( rbct0 , myThid )
171 CALL EXCH_XYZ_RS( rbct1 , myThid )
172 ENDIF
173 IF ( useRBCsalt .AND. relaxSFile .NE. ' ' ) THEN
174 IF ( rbcsSingleTimeFiles ) THEN
175 IL=ILNBLNK( relaxSFile )
176 WRITE(fullName,'(2a,i10.10)') relaxSFile(1:IL),'.',initer0
177 CALL READ_REC_XYZ_RS(fullName, rbcs0, 1, myIter, myThid)
178 WRITE(fullName,'(2a,i10.10)') relaxSFile(1:IL),'.',initer1
179 CALL READ_REC_XYZ_RS(fullName, rbcs1, 1, myIter, myThid)
180 ELSE
181 CALL READ_REC_XYZ_RS(relaxSFile,rbcs0,intime0,myIter,myThid)
182 CALL READ_REC_XYZ_RS(relaxSFile,rbcs1,intime1,myIter,myThid)
183 ENDIF
184 CALL EXCH_XYZ_RS( rbcs0 , myThid )
185 CALL EXCH_XYZ_RS( rbcs1 , myThid )
186 ENDIF
187
188 #ifdef ALLOW_PTRACERS
189 IF ( usePTRACERS ) THEN
190 DO iTracer = 1, PTRACERS_numInUse
191 IF ( useRBCptrnum(iTracer) .AND.
192 & relaxPtracerFile(iTracer).NE. ' ' ) THEN
193 IF ( rbcsSingleTimeFiles ) THEN
194 IL=ILNBLNK( relaxPtracerFile(iTracer) )
195 WRITE(fullName,'(2a,i10.10)') relaxPtracerFile(iTracer)(1:IL)
196 & ,'.',initer0
197 CALL READ_REC_XYZ_RS( fullName,
198 & rbcptr0(1-Olx,1-Oly,1,1,1,iTracer),
199 & 1, myIter, myThid )
200 WRITE(fullName,'(2a,i10.10)') relaxPtracerFile(iTracer)(1:IL)
201 & ,'.',initer1
202 CALL READ_REC_XYZ_RS( fullName,
203 & rbcptr1(1-Olx,1-Oly,1,1,1,iTracer),
204 & 1, myIter, myThid )
205 ELSE
206 CALL READ_REC_XYZ_RS( relaxPtracerFile(iTracer),
207 & rbcptr0(1-Olx,1-Oly,1,1,1,iTracer),
208 & intime0, myIter, myThid )
209 CALL READ_REC_XYZ_RS( relaxPtracerFile(iTracer),
210 & rbcptr1(1-Olx,1-Oly,1,1,1,iTracer),
211 & intime1, myIter, myThid )
212 ENDIF
213 CALL EXCH_XYZ_RS( rbcptr0(1-Olx,1-Oly,1,1,1,iTracer),myThid )
214 CALL EXCH_XYZ_RS( rbcptr1(1-Olx,1-Oly,1,1,1,iTracer),myThid )
215 ENDIF
216 ENDDO
217 ENDIF
218 #endif /* ALLOW_PTRACERS */
219
220 C- save newly loaded time-record
221 DO bj = myByLo(myThid), myByHi(myThid)
222 DO bi = myBxLo(myThid), myBxHi(myThid)
223 rbcsLdRec(bi,bj) = intime1
224 ENDDO
225 ENDDO
226
227 C-- end if-block for loading new time-records
228 ENDIF
229
230 C-- Interpolate
231 DO bj = myByLo(myThid), myByHi(myThid)
232 DO bi = myBxLo(myThid), myBxHi(myThid)
233 #ifndef DISABLE_RBCS_MOM
234 IF ( useRBCuVel .OR. useRBCvVel ) THEN
235 DO k=1,Nr
236 DO j=1-Oly,sNy+Oly
237 DO i=1-Olx,sNx+Olx
238 RBCuVel(i,j,k,bi,bj) = bWght*rbcu0(i,j,k,bi,bj)
239 & +aWght*rbcu1(i,j,k,bi,bj)
240 RBCvVel(i,j,k,bi,bj) = bWght*rbcv0(i,j,k,bi,bj)
241 & +aWght*rbcv1(i,j,k,bi,bj)
242 ENDDO
243 ENDDO
244 ENDDO
245 ENDIF
246 #endif /* DISABLE_RBCS_MOM */
247 DO k=1,Nr
248 DO j=1-Oly,sNy+Oly
249 DO i=1-Olx,sNx+Olx
250 RBCtemp(i,j,k,bi,bj) = bWght*rbct0(i,j,k,bi,bj)
251 & +aWght*rbct1(i,j,k,bi,bj)
252 RBCsalt(i,j,k,bi,bj) = bWght*rbcs0(i,j,k,bi,bj)
253 & +aWght*rbcs1(i,j,k,bi,bj)
254 ENDDO
255 ENDDO
256 ENDDO
257 ENDDO
258 ENDDO
259
260 #ifdef ALLOW_PTRACERS
261 IF ( usePTRACERS ) THEN
262 DO iTracer = 1, PTRACERS_numInUse
263 IF (useRBCptrnum(iTracer)) THEN
264 DO bj = myByLo(myThid), myByHi(myThid)
265 DO bi = myBxLo(myThid), myBxHi(myThid)
266 DO k=1,Nr
267 DO j=1-Oly,sNy+Oly
268 DO i=1-Olx,sNx+Olx
269 RBC_ptracers(i,j,k,bi,bj,iTracer) =
270 & bWght*rbcptr0(i,j,k,bi,bj,iTracer)
271 & +aWght*rbcptr1(i,j,k,bi,bj,iTracer)
272 ENDDO
273 ENDDO
274 ENDDO
275 ENDDO
276 ENDDO
277 ENDIF
278 ENDDO
279 ENDIF
280 #endif /* ALLOW_PTRACERS */
281
282 CALL TIMER_STOP ('RBCS_FIELDS_LOAD [I/O]', myThid)
283
284 #endif /* ALLOW_RBCS */
285
286 RETURN
287 END

  ViewVC Help
Powered by ViewVC 1.1.22