/[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.5 - (show annotations) (download)
Wed Nov 1 20:49:18 2006 UTC (17 years, 7 months ago) by stephd
Branch: MAIN
CVS Tags: checkpoint58u_post, checkpoint58w_post, checkpoint58r_post, checkpoint58x_post, checkpoint58t_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59h, checkpoint59, checkpoint58y_post, checkpoint58v_post, checkpoint58s_post
Changes since 1.4: +10 -8 lines
o fix bug in how the ptracer rbcs values were being read and exchanged

1
2 #include "CPP_OPTIONS.h"
3 #include "PACKAGES_CONFIG.h"
4
5 C !ROUTINE: RBCS_FIELDS_LOAD
6 C !INTERFACE:
7 SUBROUTINE RBCS_FIELDS_LOAD( myTime, myIter, myThid )
8 C *==========================================================*
9 C | SUBROUTINE RBCS_FIELDS_LOAD
10 C | o Control reading of fields from external source.
11 C *==========================================================*
12 C | Offline External source field loading routine.
13 C | This routine is called every time we want to
14 C | load a a set of external fields. The routine decides
15 C | which fields to load and then reads them in.
16 C | This routine needs to be customised for particular
17 C | experiments.
18 C *==========================================================*
19
20 C !USES:
21 IMPLICIT NONE
22 C === Global variables ===
23 #include "SIZE.h"
24 #include "EEPARAMS.h"
25 #include "PARAMS.h"
26 #include "FFIELDS.h"
27 #include "GRID.h"
28 #include "DYNVARS.h"
29 #ifdef ALLOW_PTRACERS
30 #include "PTRACERS_SIZE.h"
31 #include "PTRACERS.h"
32 #endif
33 #include "RBCS.h"
34
35 C !INPUT/OUTPUT PARAMETERS:
36 C === Routine arguments ===
37 C myThid - Thread no. that called this routine.
38 C myTime - Simulation time
39 C myIter - Simulation timestep number
40 INTEGER myThid
41 _RL myTime
42 INTEGER myIter
43
44 c fn :: Temp. for building file name.
45 CHARACTER*(MAX_LEN_FNAM) fn
46 CHARACTER*(MAX_LEN_FNAM) fn2
47 INTEGER prec
48
49
50
51 C !LOCAL VARIABLES:
52 C === Local arrays ===
53 C [01] :: End points for interpolation
54 C Above use static heap storage to allow exchange.
55 C aWght, bWght :: Interpolation weights
56
57 INTEGER bi,bj,i,j,k,intime0,intime1
58 _RL aWght,bWght,rdt
59 INTEGER nForcingPeriods,Imytm,Ifprd,Ifcyc,Iftm
60 INTEGER I1, I2
61 INTEGER iTracer
62 INTEGER IFNBLNK, ILNBLNK
63 EXTERNAL IFNBLNK, ILNBLNK
64
65 #ifdef ALLOW_RBCS
66 CALL TIMER_START('RBCS_FIELDS_LOAD [I/O]', myThid)
67 prec = readBinaryPrec
68
69
70 C First call requires that we initialize everything to zero for safety
71 IF ( myIter .EQ. nIter0 ) THEN
72 DO bj = myByLo(myThid), myByHi(myThid)
73 DO bi = myBxLo(myThid), myBxHi(myThid)
74 do k=1,Nr
75 DO j=1-Oly,sNy+Oly
76 DO i=1-Olx,sNx+Olx
77 rbct0(i,j,k,bi,bj)=0.d0
78 rbcs0(i,j,k,bi,bj)=0.d0
79 rbct1(i,j,k,bi,bj)=0.d0
80 rbcs1(i,j,k,bi,bj)=0.d0
81 ENDDO
82 ENDDO
83 enddo
84 ENDDO
85 ENDDO
86 #ifdef ALLOW_PTRACERS
87 DO iTracer = 1, PTRACERS_numInUse
88 DO bj = myByLo(myThid), myByHi(myThid)
89 DO bi = myBxLo(myThid), myBxHi(myThid)
90 do k=1,Nr
91 DO j=1-Oly,sNy+Oly
92 DO i=1-Olx,sNx+Olx
93 rbcptr0(i,j,k,bi,bj,iTracer)=0.d0
94 rbcptr1(i,j,k,bi,bj,iTracer)=0.d0
95 ENDDO
96 ENDDO
97 enddo
98 ENDDO
99 ENDDO
100 ENDDO
101 #endif
102 ENDIF
103
104 C Now calculate whether it is time to update the forcing arrays
105 if (rbcsForcingCycle.gt.0.d0) then
106 rdt=1. _d 0 / deltaTclock
107 nForcingPeriods=int(rbcsForcingCycle/rbcsForcingPeriod+0.5)
108 Imytm=int((myTime-float(rbcsIniter)*deltaTclock)*rdt+0.5)
109 Ifprd=int(rbcsForcingPeriod*rdt+0.5)
110 Ifcyc=int(rbcsForcingCycle*rdt+0.5)
111 Iftm=mod( Imytm+Ifcyc-Ifprd/2 ,Ifcyc)
112
113 intime0=int(Iftm/Ifprd)
114 intime1=mod(intime0+1,nForcingPeriods)
115 aWght=float( Iftm-Ifprd*intime0 )/float( Ifprd )
116 bWght=1.-aWght
117
118 intime0=intime0+1
119 INTIME1=intime1+1
120 else
121 intime1=1
122 intime0=1
123 Iftm=1
124 Ifprd=0
125 aWght=.5d0
126 bWght=.5d0
127 endif
128
129 IF (
130 & Iftm-Ifprd*(intime0-1) .EQ. 0
131 & .OR. myIter .EQ. nIter0
132 & ) THEN
133
134 _BEGIN_MASTER(myThid)
135
136 C If the above condition is met then we need to read in
137 C data for the period ahead and the period behind myTime.
138 WRITE(*,*)
139 & 'S/R RBCS_FIELDS_LOAD: Reading new data',myTime,myIter
140 & , nIter0, intime0,intime1
141
142 c
143 IF ( relaxTFile .NE. ' ' ) THEN
144 CALL MDSREADFIELD ( relaxTFile, prec,
145 & 'RS', Nr, rbct0, intime0, myThid )
146 CALL MDSREADFIELD ( relaxTFile, prec,
147 & 'RS', Nr, rbct1, intime1, myThid )
148 ENDIF
149 IF ( relaxSFile .NE. ' ' ) THEN
150 CALL MDSREADFIELD ( relaxSFile, prec,
151 & 'RS', Nr, rbcs0, intime0, myThid )
152 CALL MDSREADFIELD ( relaxSFile, prec,
153 & 'RS', Nr, rbcs1, intime1, myThid )
154 ENDIF
155
156 #ifdef ALLOW_PTRACERS
157 if (useRBCptracers) then
158 DO iTracer = 1, PTRACERS_numInUse
159 if (useRBCptrnum(iTracer)) then
160 WRITE(fn,'(A)') relaxPtracerFile(iTracer)
161 CALL MDSREADFIELD ( fn, prec,
162 & 'RS', Nr, rbcptr0(1-Olx,1-Oly,1,1,1,iTracer),
163 & intime0, myThid )
164 CALL MDSREADFIELD ( fn, prec,
165 & 'RS', Nr, rbcptr1(1-Olx,1-Oly,1,1,1,iTracer),
166 & intime1, myThid )
167 endif
168 ENDDO
169 endif
170 #endif
171
172 c
173
174 _END_MASTER(myThid)
175
176 C
177 _EXCH_XYZ_R4(rbct0 , myThid )
178 _EXCH_XYZ_R4(rbct1 , myThid )
179 _EXCH_XYZ_R4(rbcs0 , myThid )
180 _EXCH_XYZ_R4(rbcs1 , myThid )
181 #ifdef ALLOW_PTRACERS
182 if (useRBCptracers) then
183 DO iTracer = 1, PTRACERS_numInUse
184 _EXCH_XYZ_R4(rbcptr0(1-Olx,1-Oly,1,1,1,iTracer),myThid)
185 _EXCH_XYZ_R4(rbcptr1(1-Olx,1-Oly,1,1,1,iTracer),myThid)
186 ENDDO
187 endif
188 #endif
189
190 c
191 ENDIF
192 c
193
194 C-- Interpolate
195 DO bj = myByLo(myThid), myByHi(myThid)
196 DO bi = myBxLo(myThid), myBxHi(myThid)
197 do k=1,Nr
198 DO j=1-Oly,sNy+Oly
199 DO i=1-Olx,sNx+Olx
200 RBCtemp(i,j,k,bi,bj) = bWght*rbct0(i,j,k,bi,bj)
201 & +aWght*rbct1(i,j,k,bi,bj)
202 RBCsalt(i,j,k,bi,bj) = bWght*rbcs0(i,j,k,bi,bj)
203 & +aWght*rbcs1(i,j,k,bi,bj)
204 ENDDO
205 ENDDO
206 ENDDO
207 ENDDO
208 ENDDO
209
210 #ifdef ALLOW_PTRACERS
211 if (useRBCptracers) then
212 DO iTracer = 1, PTRACERS_numInUse
213 if (useRBCptrnum(iTracer)) then
214 DO bj = myByLo(myThid), myByHi(myThid)
215 DO bi = myBxLo(myThid), myBxHi(myThid)
216 do k=1,Nr
217 DO j=1-Oly,sNy+Oly
218 DO i=1-Olx,sNx+Olx
219 RBC_ptracers(i,j,k,bi,bj,iTracer) =
220 & bWght*rbcptr0(i,j,k,bi,bj,iTracer)
221 & +aWght*rbcptr1(i,j,k,bi,bj,iTracer)
222 ENDDO
223 ENDDO
224 ENDDO
225 ENDDO
226 ENDDO
227 endif
228 ENDDO
229 endif
230 #endif
231
232 CALL TIMER_STOP ('RBCS_FIELDS_LOAD [I/O]', myThid)
233
234 #endif
235 c! ALLOW_RBCS
236
237 RETURN
238 END
239

  ViewVC Help
Powered by ViewVC 1.1.22