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

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

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


Revision 1.12 - (hide annotations) (download)
Sun Mar 6 23:33:55 2011 UTC (13 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62v, checkpoint62u
Changes since 1.11: +1 -2 lines
remove unused variable

1 jmc 1.12 C $Header: /u/gcmpack/MITgcm/pkg/rbcs/rbcs_fields_load.F,v 1.11 2010/11/10 00:34:21 jahn Exp $
2 jmc 1.6 C $Name: $
3 stephd 1.1
4 jmc 1.10 #include "RBCS_OPTIONS.h"
5 jmc 1.6
6 stephd 1.1 C !ROUTINE: RBCS_FIELDS_LOAD
7     C !INTERFACE:
8     SUBROUTINE RBCS_FIELDS_LOAD( myTime, myIter, myThid )
9     C *==========================================================*
10 jmc 1.6 C | SUBROUTINE RBCS_FIELDS_LOAD
11     C | o Control reading of fields from external source.
12 stephd 1.1 C *==========================================================*
13 jmc 1.6 C | Offline External source field loading routine.
14     C | This routine is called every time we want to
15     C | load a a set of external fields. The routine decides
16     C | which fields to load and then reads them in.
17     C | This routine needs to be customised for particular
18     C | experiments.
19 stephd 1.1 C *==========================================================*
20    
21     C !USES:
22     IMPLICIT NONE
23     C === Global variables ===
24     #include "SIZE.h"
25     #include "EEPARAMS.h"
26     #include "PARAMS.h"
27     #include "FFIELDS.h"
28     #include "GRID.h"
29     #include "DYNVARS.h"
30     #ifdef ALLOW_PTRACERS
31     #include "PTRACERS_SIZE.h"
32 jmc 1.7 #include "PTRACERS_PARAMS.h"
33 stephd 1.1 #endif
34     #include "RBCS.h"
35    
36     C !INPUT/OUTPUT PARAMETERS:
37     C === Routine arguments ===
38 jmc 1.7 C myTime :: Simulation time
39     C myIter :: Simulation timestep number
40     C myThid :: Thread no. that called this routine.
41 stephd 1.1 _RL myTime
42     INTEGER myIter
43 jmc 1.7 INTEGER myThid
44 stephd 1.1
45 jmc 1.10 C !FUNCTIONS:
46     INTEGER IFNBLNK, ILNBLNK
47     EXTERNAL IFNBLNK, ILNBLNK
48    
49 stephd 1.1 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,intime0,intime1
56 jahn 1.11 _RL aWght,bWght,rhalfdt
57     INTEGER nForcingPeriods,Imytm,Ifprd,Ifcyc,Iftm,Ifmod
58 jmc 1.10 #ifdef ALLOW_PTRACERS
59 stephd 1.1 INTEGER iTracer
60 jmc 1.10 #endif
61 jahn 1.11 INTEGER IL, initer0, initer1
62     CHARACTER*(MAX_LEN_FNAM) fullName
63    
64     INTEGER F90MODULO,arg1,arg2
65     C statement function to emulate Fortran 90 MODULO
66     C this modulo has the same sign as arg2 (and absolute value < |arg2|)
67     F90MODULO(arg1,arg2) = MOD(MOD(arg1,arg2)+arg2,arg2)
68 stephd 1.1
69     #ifdef ALLOW_RBCS
70     CALL TIMER_START('RBCS_FIELDS_LOAD [I/O]', myThid)
71    
72     C First call requires that we initialize everything to zero for safety
73     IF ( myIter .EQ. nIter0 ) THEN
74     DO bj = myByLo(myThid), myByHi(myThid)
75 jmc 1.10 DO bi = myBxLo(myThid), myBxHi(myThid)
76     DO k=1,Nr
77     DO j=1-Oly,sNy+Oly
78     DO i=1-Olx,sNx+Olx
79     rbct0(i,j,k,bi,bj)=0. _d 0
80     rbcs0(i,j,k,bi,bj)=0. _d 0
81     rbct1(i,j,k,bi,bj)=0. _d 0
82     rbcs1(i,j,k,bi,bj)=0. _d 0
83     ENDDO
84 stephd 1.1 ENDDO
85     ENDDO
86 jmc 1.7 ENDDO
87 stephd 1.1 ENDDO
88     #ifdef ALLOW_PTRACERS
89     DO iTracer = 1, PTRACERS_numInUse
90     DO bj = myByLo(myThid), myByHi(myThid)
91 jmc 1.10 DO bi = myBxLo(myThid), myBxHi(myThid)
92     DO k=1,Nr
93     DO j=1-Oly,sNy+Oly
94     DO i=1-Olx,sNx+Olx
95     rbcptr0(i,j,k,bi,bj,iTracer)=0. _d 0
96     rbcptr1(i,j,k,bi,bj,iTracer)=0. _d 0
97     ENDDO
98 stephd 1.1 ENDDO
99     ENDDO
100 jmc 1.7 ENDDO
101 stephd 1.1 ENDDO
102     ENDDO
103     #endif
104     ENDIF
105    
106     C Now calculate whether it is time to update the forcing arrays
107 jahn 1.11 IF (rbcsForcingPeriod.GT.0. _d 0) THEN
108     C this converts times to even integers
109     rhalfdt = 2. _d 0 / deltaTclock
110 jmc 1.8 nForcingPeriods = NINT(rbcsForcingCycle/rbcsForcingPeriod)
111 jahn 1.11 Imytm = NINT( (myTime-rbcsForcingOffset)*rhalfdt )
112     Ifprd = NINT(rbcsForcingPeriod*rhalfdt)
113     Ifcyc = NINT(rbcsForcingCycle*rhalfdt)
114     Iftm = Imytm-Ifprd/2
115     Ifmod = F90MODULO(Iftm,Ifprd)
116    
117     intime0 = (Iftm-Ifmod)/Ifprd
118     intime1 = intime0 + 1
119     IF (rbcsForcingCycle.GT.0. _d 0) THEN
120     intime0 = F90MODULO(intime0,nForcingPeriods)
121     intime1 = F90MODULO(intime1,nForcingPeriods)
122     ENDIF
123     intime0 = 1 + intime0
124     intime1 = 1 + intime1
125 jmc 1.8
126     c aWght = DFLOAT( Iftm-Ifprd*(intime0 - 1) ) / DFLOAT( Ifprd )
127 jahn 1.11 aWght = FLOAT( Ifmod )
128 jmc 1.8 bWght = FLOAT( Ifprd )
129     aWght = aWght / bWght
130     bWght = 1. _d 0 - aWght
131 jmc 1.6
132 jmc 1.7 ELSE
133 jmc 1.8 intime1 = 1
134     intime0 = 1
135 jahn 1.11 Ifmod = 1
136 jmc 1.8 aWght = .5 _d 0
137     bWght = .5 _d 0
138 jmc 1.7 ENDIF
139 stephd 1.1
140 jahn 1.11 C for rbcsSingleTimeFiles=.TRUE.
141     Ifprd = NINT(rbcsForcingPeriod/deltaTrbcs)
142     initer0 = rbcsIter0 + intime0*Ifprd
143     initer1 = rbcsIter0 + intime1*Ifprd
144    
145 stephd 1.1 IF (
146 jahn 1.11 & Ifmod .EQ. 0
147 stephd 1.1 & .OR. myIter .EQ. nIter0
148     & ) THEN
149    
150     C If the above condition is met then we need to read in
151     C data for the period ahead and the period behind myTime.
152 jmc 1.7 _BEGIN_MASTER(myThid)
153 jmc 1.10 WRITE(standardMessageUnit,'(A,2I5,I10,1P1E20.12)')
154     & 'S/R RBCS_FIELDS_LOAD: Reading new data:',
155     & intime0, intime1, myIter, myTime
156 jmc 1.7 _END_MASTER(myThid)
157 stephd 1.1
158 jmc 1.10 IF ( useRBCtemp .AND. relaxTFile .NE. ' ' ) THEN
159 jahn 1.11 IF ( rbcsSingleTimeFiles ) THEN
160     IL=ILNBLNK( relaxTFile )
161     WRITE(fullName,'(2a,i10.10)') relaxTFile(1:IL),'.',initer0
162     CALL READ_REC_XYZ_RS(fullName, rbct0, 1, myIter, myThid)
163     WRITE(fullName,'(2a,i10.10)') relaxTFile(1:IL),'.',initer1
164     CALL READ_REC_XYZ_RS(fullName, rbct1, 1, myIter, myThid)
165     ELSE
166     CALL READ_REC_XYZ_RS(relaxTFile,rbct0,intime0,myIter,myThid)
167     CALL READ_REC_XYZ_RS(relaxTFile,rbct1,intime1,myIter,myThid)
168     ENDIF
169 stephd 1.1 ENDIF
170 jmc 1.10 IF ( useRBCsalt .AND. relaxSFile .NE. ' ' ) THEN
171 jahn 1.11 IF ( rbcsSingleTimeFiles ) THEN
172     IL=ILNBLNK( relaxSFile )
173     WRITE(fullName,'(2a,i10.10)') relaxSFile(1:IL),'.',initer0
174     CALL READ_REC_XYZ_RS(fullName, rbcs0, 1, myIter, myThid)
175     WRITE(fullName,'(2a,i10.10)') relaxSFile(1:IL),'.',initer1
176     CALL READ_REC_XYZ_RS(fullName, rbcs1, 1, myIter, myThid)
177     ELSE
178     CALL READ_REC_XYZ_RS(relaxSFile,rbcs0,intime0,myIter,myThid)
179     CALL READ_REC_XYZ_RS(relaxSFile,rbcs1,intime1,myIter,myThid)
180     ENDIF
181 stephd 1.1 ENDIF
182    
183     #ifdef ALLOW_PTRACERS
184 jmc 1.10 IF ( usePTRACERS ) THEN
185 jmc 1.7 DO iTracer = 1, PTRACERS_numInUse
186 jmc 1.10 IF ( useRBCptrnum(iTracer) .AND.
187     & relaxPtracerFile(iTracer).NE. ' ' ) THEN
188 jahn 1.11 IF ( rbcsSingleTimeFiles ) THEN
189     IL=ILNBLNK( relaxPtracerFile(iTracer) )
190     WRITE(fullName,'(2a,i10.10)') relaxPtracerFile(iTracer)(1:IL)
191     & ,'.',initer0
192     CALL READ_REC_XYZ_RS( fullName,
193     & rbcptr0(1-Olx,1-Oly,1,1,1,iTracer),
194     & 1, myIter, myThid )
195     WRITE(fullName,'(2a,i10.10)') relaxPtracerFile(iTracer)(1:IL)
196     & ,'.',initer1
197     CALL READ_REC_XYZ_RS( fullName,
198     & rbcptr1(1-Olx,1-Oly,1,1,1,iTracer),
199     & 1, myIter, myThid )
200     ELSE
201 jmc 1.7 CALL READ_REC_XYZ_RS( relaxPtracerFile(iTracer),
202     & rbcptr0(1-Olx,1-Oly,1,1,1,iTracer),
203     & intime0, myIter, myThid )
204     CALL READ_REC_XYZ_RS( relaxPtracerFile(iTracer),
205     & rbcptr1(1-Olx,1-Oly,1,1,1,iTracer),
206     & intime1, myIter, myThid )
207 jahn 1.11 ENDIF
208 jmc 1.7 ENDIF
209     ENDDO
210     ENDIF
211 stephd 1.1 #endif
212    
213 jmc 1.10 IF ( useRBCtemp .AND. relaxTFile .NE. ' ' ) THEN
214     CALL EXCH_XYZ_RS( rbct0 , myThid )
215     CALL EXCH_XYZ_RS( rbct1 , myThid )
216     ENDIF
217     IF ( useRBCsalt .AND. relaxSFile .NE. ' ' ) THEN
218     CALL EXCH_XYZ_RS( rbcs0 , myThid )
219     CALL EXCH_XYZ_RS( rbcs1 , myThid )
220     ENDIF
221 stephd 1.1 #ifdef ALLOW_PTRACERS
222 jmc 1.10 IF (usePTRACERS) THEN
223 jmc 1.7 DO iTracer = 1, PTRACERS_numInUse
224 jmc 1.10 IF ( useRBCptrnum(iTracer) ) THEN
225     CALL EXCH_XYZ_RS( rbcptr0(1-Olx,1-Oly,1,1,1,iTracer),myThid )
226     CALL EXCH_XYZ_RS( rbcptr1(1-Olx,1-Oly,1,1,1,iTracer),myThid )
227     ENDIF
228 jmc 1.7 ENDDO
229     ENDIF
230 jmc 1.10 #endif /* ALLOW_PTRACERS */
231 jmc 1.6
232 stephd 1.1 ENDIF
233 jmc 1.6
234     C-- Interpolate
235 stephd 1.1 DO bj = myByLo(myThid), myByHi(myThid)
236     DO bi = myBxLo(myThid), myBxHi(myThid)
237 jmc 1.7 DO k=1,Nr
238     DO j=1-Oly,sNy+Oly
239     DO i=1-Olx,sNx+Olx
240     RBCtemp(i,j,k,bi,bj) = bWght*rbct0(i,j,k,bi,bj)
241     & +aWght*rbct1(i,j,k,bi,bj)
242     RBCsalt(i,j,k,bi,bj) = bWght*rbcs0(i,j,k,bi,bj)
243     & +aWght*rbcs1(i,j,k,bi,bj)
244     ENDDO
245 stephd 1.1 ENDDO
246     ENDDO
247     ENDDO
248     ENDDO
249    
250     #ifdef ALLOW_PTRACERS
251 jmc 1.10 IF ( usePTRACERS ) THEN
252 jmc 1.7 DO iTracer = 1, PTRACERS_numInUse
253     IF (useRBCptrnum(iTracer)) THEN
254     DO bj = myByLo(myThid), myByHi(myThid)
255 stephd 1.1 DO bi = myBxLo(myThid), myBxHi(myThid)
256 jmc 1.7 DO k=1,Nr
257     DO j=1-Oly,sNy+Oly
258     DO i=1-Olx,sNx+Olx
259     RBC_ptracers(i,j,k,bi,bj,iTracer) =
260 stephd 1.5 & bWght*rbcptr0(i,j,k,bi,bj,iTracer)
261     & +aWght*rbcptr1(i,j,k,bi,bj,iTracer)
262 jmc 1.7 ENDDO
263 stephd 1.1 ENDDO
264     ENDDO
265     ENDDO
266 jmc 1.7 ENDDO
267     ENDIF
268     ENDDO
269     ENDIF
270 jmc 1.10 #endif /* ALLOW_PTRACERS */
271 stephd 1.1
272 jmc 1.7 CALL TIMER_STOP ('RBCS_FIELDS_LOAD [I/O]', myThid)
273 stephd 1.1
274 jmc 1.7 #endif /* ALLOW_RBCS */
275 stephd 1.1
276     RETURN
277     END

  ViewVC Help
Powered by ViewVC 1.1.22