/[MITgcm]/MITgcm/model/src/external_fields_load.F
ViewVC logotype

Contents of /MITgcm/model/src/external_fields_load.F

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


Revision 1.33 - (show annotations) (download)
Sun Jun 14 21:45:12 2009 UTC (14 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62c, checkpoint62a, checkpoint62d, checkpoint62, checkpoint62b, checkpoint61q, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.32: +1 -7 lines
remove unnecessary BARRIER

1 C $Header: /u/gcmpack/MITgcm/model/src/external_fields_load.F,v 1.32 2009/04/28 18:01:14 jmc Exp $
2 C $Name: $
3
4 #include "PACKAGES_CONFIG.h"
5 #include "CPP_OPTIONS.h"
6
7 CBOP
8 C !ROUTINE: EXTERNAL_FIELDS_LOAD
9 C !INTERFACE:
10 SUBROUTINE EXTERNAL_FIELDS_LOAD( myTime, myIter, myThid )
11 C !DESCRIPTION: \bv
12 C *==========================================================*
13 C | SUBROUTINE EXTERNAL_FIELDS_LOAD
14 C | o Control reading of fields from external source.
15 C *==========================================================*
16 C | External source field loading routine.
17 C | This routine is called every time we want to
18 C | load a a set of external fields. The routine decides
19 C | which fields to load and then reads them in.
20 C | This routine needs to be customised for particular
21 C | experiments.
22 C | Notes
23 C | =====
24 C | Two-dimensional and three-dimensional I/O are handled in
25 C | the following way under MITgcmUV. A master thread
26 C | performs I/O using system calls. This threads reads data
27 C | into a temporary buffer. At present the buffer is loaded
28 C | with the entire model domain. This is probably OK for now
29 C | Each thread then copies data from the buffer to the
30 C | region of the proper array it is responsible for.
31 C | =====
32 C | Conversion of flux fields are described in FFIELDS.h
33 C *==========================================================*
34 C \ev
35
36 C !USES:
37 IMPLICIT NONE
38 C === Global variables ===
39 #include "SIZE.h"
40 #include "EEPARAMS.h"
41 #include "PARAMS.h"
42 #include "FFIELDS.h"
43 #include "GRID.h"
44 #include "DYNVARS.h"
45
46 C !INPUT/OUTPUT PARAMETERS:
47 C === Routine arguments ===
48 C myThid - Thread no. that called this routine.
49 C myTime - Simulation time
50 C myIter - Simulation timestep number
51 INTEGER myThid
52 _RL myTime
53 INTEGER myIter
54
55 #ifndef EXCLUDE_FFIELDS_LOAD
56
57 C !LOCAL VARIABLES:
58 C === Local arrays ===
59 C aWght, bWght :: Interpolation weights
60 INTEGER bi,bj,i,j,intime0,intime1
61 _RL aWght,bWght,rdt
62 _RL tmp1Wght, tmp2Wght
63 INTEGER nForcingPeriods,Imytm,Ifprd,Ifcyc,Iftm
64 CEOP
65
66 IF ( periodicExternalForcing ) THEN
67
68 C First call requires that we initialize everything to zero for safety
69 cph has been shifted to ini_forcing.F
70
71 C Now calculate whether it is time to update the forcing arrays
72 rdt = 1. _d 0 / deltaTclock
73 nForcingPeriods = NINT(externForcingCycle/externForcingPeriod)
74 Imytm = NINT(myTime*rdt)
75 Ifprd = NINT(externForcingPeriod*rdt)
76 Ifcyc = NINT(externForcingCycle*rdt)
77 Imytm = Imytm + Ifcyc*( 1 - NINT(myTime/externForcingCycle) )
78 Iftm = MOD( Imytm+Ifcyc-Ifprd/2, Ifcyc)
79
80 intime0 = 1 + INT(Iftm/Ifprd)
81 intime1 = 1 + MOD(intime0,nForcingPeriods)
82 C-jmc: with some option of g77, FLOAT results in real*4 evaluation
83 C of aWght; using DFLOAT always force real*8 computation:
84 c aWght = DFLOAT( Iftm-Ifprd*(intime0 - 1) ) / DFLOAT( Ifprd )
85 C-ph: however, TAF doesnt recognize DFLOAT,
86 C-jmc: so let's try this:
87 tmp1Wght = FLOAT( Iftm-Ifprd*(intime0 - 1) )
88 tmp2Wght = FLOAT( Ifprd )
89 aWght = tmp1Wght / tmp2Wght
90 bWght = 1. _d 0 - aWght
91
92 IF (
93 & Iftm-Ifprd*(intime0-1) .EQ. 0
94 & .OR. myIter .EQ. nIter0
95 & ) THEN
96
97 C If the above condition is met then we need to read in
98 C data for the period ahead and the period behind myTime.
99 _BEGIN_MASTER(myThid)
100 WRITE(standardMessageUnit,'(A,2I5,I10,1P1E20.12)')
101 & 'S/R EXTERNAL_FIELDS_LOAD: Reading new data:',
102 & intime0, intime1, myIter, myTime
103 _END_MASTER(myThid)
104
105 IF ( zonalWindFile .NE. ' ' ) THEN
106 CALL READ_REC_XY_RS( zonalWindFile, taux0,
107 & intime0, myIter, myThid )
108 CALL READ_REC_XY_RS( zonalWindFile, taux1,
109 & intime1, myIter, myThid )
110 ENDIF
111 IF ( meridWindFile .NE. ' ' ) THEN
112 CALL READ_REC_XY_RS( meridWindFile, tauy0,
113 & intime0, myIter, myThid )
114 CALL READ_REC_XY_RS( meridWindFile, tauy1,
115 & intime1, myIter, myThid )
116 ENDIF
117 IF ( surfQFile .NE. ' ' ) THEN
118 CALL READ_REC_XY_RS( surfQFile, Qnet0,
119 & intime0, myIter, myThid )
120 CALL READ_REC_XY_RS( surfQFile, Qnet1,
121 & intime1, myIter, myThid )
122 ELSEIF ( surfQnetFile .NE. ' ' ) THEN
123 CALL READ_REC_XY_RS( surfQnetFile, Qnet0,
124 & intime0, myIter, myThid )
125 CALL READ_REC_XY_RS( surfQnetFile, Qnet1,
126 & intime1, myIter, myThid )
127 ENDIF
128 IF ( EmPmRfile .NE. ' ' ) THEN
129 CALL READ_REC_XY_RS( EmPmRfile, EmPmR0,
130 & intime0, myIter, myThid )
131 CALL READ_REC_XY_RS( EmPmRfile, EmPmR1,
132 & intime1, myIter, myThid )
133 c IF ( convertEmP2rUnit.EQ.mass2rUnit ) THEN
134 C- EmPmR is now (after c59h) expressed in kg/m2/s (fresh water mass flux)
135 DO bj = myByLo(myThid), myByHi(myThid)
136 DO bi = myBxLo(myThid), myBxHi(myThid)
137 DO j=1-Oly,sNy+Oly
138 DO i=1-Olx,sNx+Olx
139 EmPmR0(i,j,bi,bj) = EmPmR0(i,j,bi,bj)*rhoConstFresh
140 EmPmR1(i,j,bi,bj) = EmPmR1(i,j,bi,bj)*rhoConstFresh
141 ENDDO
142 ENDDO
143 ENDDO
144 ENDDO
145 c ENDIF
146 ENDIF
147 IF ( saltFluxFile .NE. ' ' ) THEN
148 CALL READ_REC_XY_RS( saltFluxFile, saltFlux0,
149 & intime0, myIter, myThid )
150 CALL READ_REC_XY_RS( saltFluxFile, saltFlux1,
151 & intime1, myIter, myThid )
152 ENDIF
153 IF ( thetaClimFile .NE. ' ' ) THEN
154 CALL READ_REC_XY_RS( thetaClimFile, SST0,
155 & intime0, myIter, myThid )
156 CALL READ_REC_XY_RS( thetaClimFile, SST1,
157 & intime1, myIter, myThid )
158 ENDIF
159 IF ( saltClimFile .NE. ' ' ) THEN
160 CALL READ_REC_XY_RS( saltClimFile, SSS0,
161 & intime0, myIter, myThid )
162 CALL READ_REC_XY_RS( saltClimFile, SSS1,
163 & intime1, myIter, myThid )
164 ENDIF
165 #ifdef SHORTWAVE_HEATING
166 IF ( surfQswFile .NE. ' ' ) THEN
167 CALL READ_REC_XY_RS( surfQswFile, Qsw0,
168 & intime0, myIter, myThid )
169 CALL READ_REC_XY_RS( surfQswFile, Qsw1,
170 & intime1, myIter, myThid )
171 IF ( surfQFile .NE. ' ' ) THEN
172 C- Qnet is now (after c54) the net Heat Flux (including SW)
173 DO bj = myByLo(myThid), myByHi(myThid)
174 DO bi = myBxLo(myThid), myBxHi(myThid)
175 DO j=1-Oly,sNy+Oly
176 DO i=1-Olx,sNx+Olx
177 Qnet0(i,j,bi,bj) = Qnet0(i,j,bi,bj) + Qsw0(i,j,bi,bj)
178 Qnet1(i,j,bi,bj) = Qnet1(i,j,bi,bj) + Qsw1(i,j,bi,bj)
179 ENDDO
180 ENDDO
181 ENDDO
182 ENDDO
183 ENDIF
184 ENDIF
185 #endif
186 #ifdef ATMOSPHERIC_LOADING
187 IF ( pLoadFile .NE. ' ' ) THEN
188 CALL READ_REC_XY_RS( pLoadFile, pLoad0,
189 & intime0, myIter, myThid )
190 CALL READ_REC_XY_RS( pLoadFile, pLoad1,
191 & intime1, myIter, myThid )
192 ENDIF
193 #endif
194
195 C- thread synchronisation (barrier) is part of the EXCH S/R calls
196 _EXCH_XY_RS(SST0 , myThid )
197 _EXCH_XY_RS(SST1 , myThid )
198 _EXCH_XY_RS(SSS0 , myThid )
199 _EXCH_XY_RS(SSS1 , myThid )
200 CALL EXCH_UV_XY_RS(taux0,tauy0,.TRUE.,myThid)
201 CALL EXCH_UV_XY_RS(taux1,tauy1,.TRUE.,myThid)
202 _EXCH_XY_RS(Qnet0, myThid )
203 _EXCH_XY_RS(Qnet1, myThid )
204 _EXCH_XY_RS(EmPmR0, myThid )
205 _EXCH_XY_RS(EmPmR1, myThid )
206 _EXCH_XY_RS(saltFlux0, myThid )
207 _EXCH_XY_RS(saltFlux1, myThid )
208 #ifdef SHORTWAVE_HEATING
209 _EXCH_XY_RS(Qsw0, myThid )
210 _EXCH_XY_RS(Qsw1, myThid )
211 #endif
212 #ifdef ATMOSPHERIC_LOADING
213 _EXCH_XY_RS(pLoad0, myThid )
214 _EXCH_XY_RS(pLoad1, myThid )
215 #endif
216
217 ENDIF
218
219 C-- Interpolate fu,fv,Qnet,EmPmR,SST,SSS,Qsw
220 DO bj = myByLo(myThid), myByHi(myThid)
221 DO bi = myBxLo(myThid), myBxHi(myThid)
222 IF ( thetaClimFile .NE. ' ' ) THEN
223 DO j=1-Oly,sNy+Oly
224 DO i=1-Olx,sNx+Olx
225 SST(i,j,bi,bj) = bWght*SST0(i,j,bi,bj)
226 & + aWght*SST1(i,j,bi,bj)
227 ENDDO
228 ENDDO
229 ENDIF
230 IF ( saltClimFile .NE. ' ' ) THEN
231 DO j=1-Oly,sNy+Oly
232 DO i=1-Olx,sNx+Olx
233 SSS(i,j,bi,bj) = bWght*SSS0(i,j,bi,bj)
234 & + aWght*SSS1(i,j,bi,bj)
235 ENDDO
236 ENDDO
237 ENDIF
238 IF ( zonalWindFile .NE. ' ' ) THEN
239 DO j=1-Oly,sNy+Oly
240 DO i=1-Olx,sNx+Olx
241 fu(i,j,bi,bj) = bWght*taux0(i,j,bi,bj)
242 & + aWght*taux1(i,j,bi,bj)
243 ENDDO
244 ENDDO
245 ENDIF
246 IF ( meridWindFile .NE. ' ' ) THEN
247 DO j=1-Oly,sNy+Oly
248 DO i=1-Olx,sNx+Olx
249 fv(i,j,bi,bj) = bWght*tauy0(i,j,bi,bj)
250 & + aWght*tauy1(i,j,bi,bj)
251 ENDDO
252 ENDDO
253 ENDIF
254 IF ( surfQnetFile .NE. ' '
255 & .OR. surfQFile .NE. ' ' ) THEN
256 DO j=1-Oly,sNy+Oly
257 DO i=1-Olx,sNx+Olx
258 Qnet(i,j,bi,bj) = bWght*Qnet0(i,j,bi,bj)
259 & + aWght*Qnet1(i,j,bi,bj)
260 ENDDO
261 ENDDO
262 ENDIF
263 IF ( EmPmRfile .NE. ' ' ) THEN
264 DO j=1-Oly,sNy+Oly
265 DO i=1-Olx,sNx+Olx
266 EmPmR(i,j,bi,bj) = bWght*EmPmR0(i,j,bi,bj)
267 & + aWght*EmPmR1(i,j,bi,bj)
268 ENDDO
269 ENDDO
270 ENDIF
271 IF ( saltFluxFile .NE. ' ' ) THEN
272 DO j=1-Oly,sNy+Oly
273 DO i=1-Olx,sNx+Olx
274 saltFlux(i,j,bi,bj) = bWght*saltFlux0(i,j,bi,bj)
275 & + aWght*saltFlux1(i,j,bi,bj)
276 ENDDO
277 ENDDO
278 ENDIF
279 #ifdef SHORTWAVE_HEATING
280 IF ( surfQswFile .NE. ' ' ) THEN
281 DO j=1-Oly,sNy+Oly
282 DO i=1-Olx,sNx+Olx
283 Qsw(i,j,bi,bj) = bWght*Qsw0(i,j,bi,bj)
284 & + aWght*Qsw1(i,j,bi,bj)
285 ENDDO
286 ENDDO
287 ENDIF
288 #endif
289 #ifdef ATMOSPHERIC_LOADING
290 IF ( pLoadFile .NE. ' ' ) THEN
291 DO j=1-Oly,sNy+Oly
292 DO i=1-Olx,sNx+Olx
293 pLoad(i,j,bi,bj) = bWght*pLoad0(i,j,bi,bj)
294 & + aWght*pLoad1(i,j,bi,bj)
295 ENDDO
296 ENDDO
297 ENDIF
298 #endif
299 ENDDO
300 ENDDO
301
302 C-- Print for checking:
303 c IF ( debugLevel.GE.debLevA .AND. myIter.LT.50+nIter0) THEN
304 IF ( debugLevel.GE.debLevA .AND. myTime.LT.62208000.) THEN
305 _BEGIN_MASTER( myThid )
306 WRITE(standardMessageUnit,'(a,1p7e12.4,2i6,2e12.4)')
307 & 'time,SST,SSS,fu,fv,Q,E-P,i0,i1,a,b = ',
308 & myTime,
309 & SST(1,sNy,1,1),SSS(1,sNy,1,1),
310 & fu(1,sNy,1,1),fv(1,sNy,1,1),
311 & Qnet(1,sNy,1,1),EmPmR(1,sNy,1,1),
312 & intime0,intime1,aWght,bWght
313 WRITE(standardMessageUnit,'(a,1p4e12.4,2E23.15)')
314 & 'time,fu0,fu1,fu = ',
315 & myTime,
316 & taux0(1,sNy,1,1),taux1(1,sNy,1,1),fu(1,sNy,1,1),
317 & aWght,bWght
318 _END_MASTER( myThid )
319 ENDIF
320
321 C endif for periodicForcing
322 ENDIF
323
324 #endif /* EXCLUDE_FFIELDS_LOAD */
325
326 RETURN
327 END

  ViewVC Help
Powered by ViewVC 1.1.22