/[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.10 - (show annotations) (download)
Tue Apr 6 20:38:18 2010 UTC (14 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62n, checkpoint62m, checkpoint62l
Changes since 1.9: +49 -41 lines
clean-up RBCS code: add RBCS_OPTIONS.h file ; fix multi-threaded ;
  change (+ fix IO calls) type of array RBC_mask from _RL to _RS.

1 C $Header: /u/gcmpack/MITgcm/pkg/rbcs/rbcs_fields_load.F,v 1.9 2009/04/28 18:18:29 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 C *==========================================================*
10 C | SUBROUTINE RBCS_FIELDS_LOAD
11 C | o Control reading of fields from external source.
12 C *==========================================================*
13 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 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 #include "PTRACERS_PARAMS.h"
33 #endif
34 #include "RBCS.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,intime0,intime1
56 _RL aWght,bWght,rdt
57 INTEGER nForcingPeriods,Imytm,Ifprd,Ifcyc,Iftm
58 #ifdef ALLOW_PTRACERS
59 INTEGER iTracer
60 #endif
61
62 #ifdef ALLOW_RBCS
63 CALL TIMER_START('RBCS_FIELDS_LOAD [I/O]', myThid)
64
65 C First call requires that we initialize everything to zero for safety
66 IF ( myIter .EQ. nIter0 ) THEN
67 DO bj = myByLo(myThid), myByHi(myThid)
68 DO bi = myBxLo(myThid), myBxHi(myThid)
69 DO k=1,Nr
70 DO j=1-Oly,sNy+Oly
71 DO i=1-Olx,sNx+Olx
72 rbct0(i,j,k,bi,bj)=0. _d 0
73 rbcs0(i,j,k,bi,bj)=0. _d 0
74 rbct1(i,j,k,bi,bj)=0. _d 0
75 rbcs1(i,j,k,bi,bj)=0. _d 0
76 ENDDO
77 ENDDO
78 ENDDO
79 ENDDO
80 ENDDO
81 #ifdef ALLOW_PTRACERS
82 DO iTracer = 1, PTRACERS_numInUse
83 DO bj = myByLo(myThid), myByHi(myThid)
84 DO bi = myBxLo(myThid), myBxHi(myThid)
85 DO k=1,Nr
86 DO j=1-Oly,sNy+Oly
87 DO i=1-Olx,sNx+Olx
88 rbcptr0(i,j,k,bi,bj,iTracer)=0. _d 0
89 rbcptr1(i,j,k,bi,bj,iTracer)=0. _d 0
90 ENDDO
91 ENDDO
92 ENDDO
93 ENDDO
94 ENDDO
95 ENDDO
96 #endif
97 ENDIF
98
99 C Now calculate whether it is time to update the forcing arrays
100 IF ( rbcsForcingCycle.GT.0. _d 0 ) THEN
101 rdt = 1. _d 0 / deltaTclock
102 nForcingPeriods = NINT(rbcsForcingCycle/rbcsForcingPeriod)
103 Imytm = NINT( (myTime-rbcsIniter*deltaTclock)*rdt )
104 Ifprd = NINT(rbcsForcingPeriod*rdt)
105 Ifcyc = NINT(rbcsForcingCycle*rdt)
106 Iftm = MOD( Imytm+Ifcyc-Ifprd/2, Ifcyc)
107
108 intime0 = 1 + INT( Iftm/Ifprd )
109 intime1 = 1 + MOD( intime0,nForcingPeriods )
110 c aWght = DFLOAT( Iftm-Ifprd*(intime0 - 1) ) / DFLOAT( Ifprd )
111 aWght = FLOAT( Iftm-Ifprd*(intime0 - 1) )
112 bWght = FLOAT( Ifprd )
113 aWght = aWght / bWght
114 bWght = 1. _d 0 - aWght
115
116 ELSE
117 intime1 = 1
118 intime0 = 1
119 Iftm = 1
120 Ifprd = 0
121 aWght = .5 _d 0
122 bWght = .5 _d 0
123 ENDIF
124
125 IF (
126 & Iftm-Ifprd*(intime0-1) .EQ. 0
127 & .OR. myIter .EQ. nIter0
128 & ) THEN
129
130 C If the above condition is met then we need to read in
131 C data for the period ahead and the period behind myTime.
132 _BEGIN_MASTER(myThid)
133 WRITE(standardMessageUnit,'(A,2I5,I10,1P1E20.12)')
134 & 'S/R RBCS_FIELDS_LOAD: Reading new data:',
135 & intime0, intime1, myIter, myTime
136 _END_MASTER(myThid)
137
138 IF ( useRBCtemp .AND. relaxTFile .NE. ' ' ) THEN
139 CALL READ_REC_XYZ_RS(relaxTFile, rbct0, intime0, myIter,myThid)
140 CALL READ_REC_XYZ_RS(relaxTFile, rbct1, intime1, myIter,myThid)
141 ENDIF
142 IF ( useRBCsalt .AND. relaxSFile .NE. ' ' ) THEN
143 CALL READ_REC_XYZ_RS(relaxSFile, rbcs0, intime0, myIter,myThid)
144 CALL READ_REC_XYZ_RS(relaxSFile, rbcs1, intime1, myIter,myThid)
145 ENDIF
146
147 #ifdef ALLOW_PTRACERS
148 IF ( usePTRACERS ) THEN
149 DO iTracer = 1, PTRACERS_numInUse
150 IF ( useRBCptrnum(iTracer) .AND.
151 & relaxPtracerFile(iTracer).NE. ' ' ) THEN
152 CALL READ_REC_XYZ_RS( relaxPtracerFile(iTracer),
153 & rbcptr0(1-Olx,1-Oly,1,1,1,iTracer),
154 & intime0, myIter, myThid )
155 CALL READ_REC_XYZ_RS( relaxPtracerFile(iTracer),
156 & rbcptr1(1-Olx,1-Oly,1,1,1,iTracer),
157 & intime1, myIter, myThid )
158 ENDIF
159 ENDDO
160 ENDIF
161 #endif
162
163 IF ( useRBCtemp .AND. relaxTFile .NE. ' ' ) THEN
164 CALL EXCH_XYZ_RS( rbct0 , myThid )
165 CALL EXCH_XYZ_RS( rbct1 , myThid )
166 ENDIF
167 IF ( useRBCsalt .AND. relaxSFile .NE. ' ' ) THEN
168 CALL EXCH_XYZ_RS( rbcs0 , myThid )
169 CALL EXCH_XYZ_RS( rbcs1 , myThid )
170 ENDIF
171 #ifdef ALLOW_PTRACERS
172 IF (usePTRACERS) THEN
173 DO iTracer = 1, PTRACERS_numInUse
174 IF ( useRBCptrnum(iTracer) ) THEN
175 CALL EXCH_XYZ_RS( rbcptr0(1-Olx,1-Oly,1,1,1,iTracer),myThid )
176 CALL EXCH_XYZ_RS( rbcptr1(1-Olx,1-Oly,1,1,1,iTracer),myThid )
177 ENDIF
178 ENDDO
179 ENDIF
180 #endif /* ALLOW_PTRACERS */
181
182 ENDIF
183
184 C-- Interpolate
185 DO bj = myByLo(myThid), myByHi(myThid)
186 DO bi = myBxLo(myThid), myBxHi(myThid)
187 DO k=1,Nr
188 DO j=1-Oly,sNy+Oly
189 DO i=1-Olx,sNx+Olx
190 RBCtemp(i,j,k,bi,bj) = bWght*rbct0(i,j,k,bi,bj)
191 & +aWght*rbct1(i,j,k,bi,bj)
192 RBCsalt(i,j,k,bi,bj) = bWght*rbcs0(i,j,k,bi,bj)
193 & +aWght*rbcs1(i,j,k,bi,bj)
194 ENDDO
195 ENDDO
196 ENDDO
197 ENDDO
198 ENDDO
199
200 #ifdef ALLOW_PTRACERS
201 IF ( usePTRACERS ) THEN
202 DO iTracer = 1, PTRACERS_numInUse
203 IF (useRBCptrnum(iTracer)) THEN
204 DO bj = myByLo(myThid), myByHi(myThid)
205 DO bi = myBxLo(myThid), myBxHi(myThid)
206 DO k=1,Nr
207 DO j=1-Oly,sNy+Oly
208 DO i=1-Olx,sNx+Olx
209 RBC_ptracers(i,j,k,bi,bj,iTracer) =
210 & bWght*rbcptr0(i,j,k,bi,bj,iTracer)
211 & +aWght*rbcptr1(i,j,k,bi,bj,iTracer)
212 ENDDO
213 ENDDO
214 ENDDO
215 ENDDO
216 ENDDO
217 ENDIF
218 ENDDO
219 ENDIF
220 #endif /* ALLOW_PTRACERS */
221
222 CALL TIMER_STOP ('RBCS_FIELDS_LOAD [I/O]', myThid)
223
224 #endif /* ALLOW_RBCS */
225
226 RETURN
227 END

  ViewVC Help
Powered by ViewVC 1.1.22