/[MITgcm]/MITgcm/verification/natl_box/code/external_fields_load.F
ViewVC logotype

Contents of /MITgcm/verification/natl_box/code/external_fields_load.F

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


Revision 1.9 - (show annotations) (download)
Fri Jul 16 01:23:19 2004 UTC (19 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint55c_post, checkpoint57b_post, checkpoint57f_pre, checkpoint55d_pre, checkpoint57a_post, checkpoint55j_post, checkpoint56b_post, checkpoint55h_post, checkpoint57e_post, checkpoint54d_post, checkpoint56c_post, checkpoint54e_post, checkpoint55b_post, checkpoint55, checkpoint55a_post, checkpoint57c_pre, checkpoint55g_post, checkpoint57d_post, checkpoint55f_post, checkpoint57a_pre, checkpoint57, checkpoint56, checkpoint54f_post, eckpoint57e_pre, checkpoint57c_post, checkpoint55e_post, checkpoint54c_post, checkpoint55i_post, checkpoint56a_post, checkpoint55d_post
Changes since 1.8: +19 -1 lines
change Qnet to always be the net heat flux, (+upward).

1 C $Header: /u/gcmpack/MITgcm/verification/natl_box/code/external_fields_load.F,v 1.8 2003/11/01 04:50:03 edhill 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 LOGICAL DIFFERENT_MULTIPLE
46 EXTERNAL DIFFERENT_MULTIPLE
47
48 C !INPUT/OUTPUT PARAMETERS:
49 C === Routine arguments ===
50 C myThid - Thread no. that called this routine.
51 C myTime - Simulation time
52 C myIter - Simulation timestep number
53 INTEGER myThid
54 _RL myTime
55 INTEGER myIter
56
57
58 #ifndef ALLOW_EXF
59
60 C !LOCAL VARIABLES:
61 C === Local arrays ===
62 C aWght, bWght :: Interpolation weights
63 INTEGER bi,bj,i,j,intime0,intime1
64 _RL aWght,bWght,rdt
65 INTEGER nForcingPeriods,Imytm,Ifprd,Ifcyc,Iftm
66 CEOP
67
68 IF ( periodicExternalForcing ) THEN
69
70 C First call requires that we initialize everything to zero for safety
71 cph has been shifted to ini_forcing.F
72 cph arrays are now globally visible
73 cph
74 cph IF ( myIter .EQ. nIter0 ) THEN
75 cph CALL LEF_ZERO( taux0 ,myThid )
76 cph CALL LEF_ZERO( tauy0 ,myThid )
77 cph CALL LEF_ZERO( Qnet0 ,myThid )
78 cph CALL LEF_ZERO( EmPmR0 ,myThid )
79 cph CALL LEF_ZERO( SST0 ,myThid )
80 cph CALL LEF_ZERO( SSS0 ,myThid )
81 cph CALL LEF_ZERO( Qsw0 ,myThid )
82 cph CALL LEF_ZERO( taux1 ,myThid )
83 cph CALL LEF_ZERO( tauy1 ,myThid )
84 cph CALL LEF_ZERO( Qnet1 ,myThid )
85 cph CALL LEF_ZERO( EmPmR1 ,myThid )
86 cph CALL LEF_ZERO( SST1 ,myThid )
87 cph CALL LEF_ZERO( SSS1 ,myThid )
88 cph CALL LEF_ZERO( Qsw1 ,myThid )
89 cph ENDIF
90
91 C Now calculate whether it is time to update the forcing arrays
92 rdt=1. _d 0 / deltaTclock
93 nForcingPeriods=int(externForcingCycle/externForcingPeriod)
94 Imytm=int(myTime*rdt)
95 Ifprd=int(externForcingPeriod*rdt)
96 Ifcyc=int(externForcingCycle*rdt)
97 Iftm=mod( Imytm ,Ifcyc)
98
99 intime0=int(Iftm/Ifprd)
100 intime1=mod(intime0+1,nForcingPeriods)
101 aWght=mod(myTime/externForcingPeriod,1.)
102 bWght=1.-aWght
103
104 intime0=intime0+1
105 intime1=intime1+1
106
107 IF (
108 & Iftm-Ifprd*(intime0-1) .EQ. 0
109 & .OR. myIter .EQ. nIter0
110 & ) THEN
111
112 _BEGIN_MASTER(myThid)
113
114 C If the above condition is met then we need to read in
115 C data for the period ahead and the period behind myTime.
116 WRITE(*,*)
117 & 'S/R EXTERNAL_FIELDS_LOAD: Reading new data',myTime,myIter
118
119 IF ( zonalWindFile .NE. ' ' ) THEN
120 CALL MDSREADFIELD ( zonalWindFile, readBinaryPrec,
121 & 'RS', 1, taux0, intime0, myThid )
122 CALL MDSREADFIELD ( zonalWindFile, readBinaryPrec,
123 & 'RS', 1, taux1, intime1, myThid )
124 ENDIF
125 IF ( meridWindFile .NE. ' ' ) THEN
126 CALL MDSREADFIELD ( meridWindFile, readBinaryPrec,
127 & 'RS', 1, tauy0, intime0, myThid )
128 CALL MDSREADFIELD ( meridWindFile, readBinaryPrec,
129 & 'RS', 1, tauy1, intime1, myThid )
130 ENDIF
131 IF ( surfQFile .NE. ' ' ) THEN
132 CALL MDSREADFIELD ( surfQFile, readBinaryPrec,
133 & 'RS', 1, Qnet0, intime0, myThid )
134 CALL MDSREADFIELD ( surfQFile, readBinaryPrec,
135 & 'RS', 1, Qnet1, intime1, myThid )
136 ELSEIF ( surfQnetFile .NE. ' ' ) THEN
137 CALL MDSREADFIELD ( surfQnetFile, readBinaryPrec,
138 & 'RS', 1, Qnet0, intime0, myThid )
139 CALL MDSREADFIELD ( surfQnetFile, readBinaryPrec,
140 & 'RS', 1, Qnet1, intime1, myThid )
141 ENDIF
142 IF ( EmPmRfile .NE. ' ' ) THEN
143 CALL MDSREADFIELD ( EmPmRfile, readBinaryPrec,
144 & 'RS', 1, EmPmR0, intime0, myThid )
145 CALL MDSREADFIELD ( EmPmRfile, readBinaryPrec,
146 & 'RS', 1, EmPmR1, intime1, myThid )
147 ENDIF
148 IF ( thetaClimFile .NE. ' ' ) THEN
149 CALL MDSREADFIELD ( thetaClimFile, readBinaryPrec,
150 & 'RS', 1, SST0, intime0, myThid )
151 CALL MDSREADFIELD ( thetaClimFile, readBinaryPrec,
152 & 'RS', 1, SST1, intime1, myThid )
153 ENDIF
154 IF ( saltClimFile .NE. ' ' ) THEN
155 CALL MDSREADFIELD ( saltClimFile, readBinaryPrec,
156 & 'RS', 1, SSS0, intime0, myThid )
157 CALL MDSREADFIELD ( saltClimFile, readBinaryPrec,
158 & 'RS', 1, SSS1, intime1, myThid )
159 ENDIF
160 #ifdef SHORTWAVE_HEATING
161 IF ( surfQswFile .NE. ' ' ) THEN
162 CALL MDSREADFIELD ( surfQswFile, readBinaryPrec,
163 & 'RS', 1, Qsw0, intime0, myThid )
164 CALL MDSREADFIELD ( surfQswFile, readBinaryPrec,
165 & 'RS', 1, Qsw1, intime1, myThid )
166 IF ( surfQFile .NE. ' ' ) THEN
167 C- Qnet is now (after c54) the net Heat Flux (including SW)
168 DO bj=1,nSy
169 DO bi=1,nSx
170 DO j=1-Oly,sNy+Oly
171 DO i=1-Olx,sNx+Olx
172 Qnet0(i,j,bi,bj) = Qnet0(i,j,bi,bj) + Qsw0(i,j,bi,bj)
173 Qnet1(i,j,bi,bj) = Qnet1(i,j,bi,bj) + Qsw1(i,j,bi,bj)
174 ENDDO
175 ENDDO
176 ENDDO
177 ENDDO
178 ENDIF
179 ENDIF
180 #endif
181
182 _END_MASTER(myThid)
183 C
184 _EXCH_XY_R4(SST0 , myThid )
185 _EXCH_XY_R4(SST1 , myThid )
186 _EXCH_XY_R4(SSS0 , myThid )
187 _EXCH_XY_R4(SSS1 , myThid )
188 c _EXCH_XY_R4(taux0 , myThid )
189 c _EXCH_XY_R4(taux1 , myThid )
190 c _EXCH_XY_R4(tauy0 , myThid )
191 c _EXCH_XY_R4(tauy1 , myThid )
192 CALL EXCH_UV_XY_RS(taux0,tauy0,.TRUE.,myThid)
193 CALL EXCH_UV_XY_RS(taux1,tauy1,.TRUE.,myThid)
194 _EXCH_XY_R4(Qnet0, myThid )
195 _EXCH_XY_R4(Qnet1, myThid )
196 _EXCH_XY_R4(EmPmR0, myThid )
197 _EXCH_XY_R4(EmPmR1, myThid )
198 #ifdef SHORTWAVE_HEATING
199 _EXCH_XY_R4(Qsw0, myThid )
200 _EXCH_XY_R4(Qsw1, myThid )
201 #endif
202 C
203 ENDIF
204
205 C-- Interpolate fu,fv,Qnet,EmPmR,SST,SSS,Qsw
206 DO bj = myByLo(myThid), myByHi(myThid)
207 DO bi = myBxLo(myThid), myBxHi(myThid)
208 DO j=1-Oly,sNy+Oly
209 DO i=1-Olx,sNx+Olx
210 SST(i,j,bi,bj) = bWght*SST0(i,j,bi,bj)
211 & +aWght*SST1(i,j,bi,bj)
212 SSS(i,j,bi,bj) = bWght*SSS0(i,j,bi,bj)
213 & +aWght*SSS1(i,j,bi,bj)
214 fu(i,j,bi,bj) = -(bWght*taux0(i,j,bi,bj)
215 & +aWght*taux1(i,j,bi,bj))
216 fv(i,j,bi,bj) = -(bWght*tauy0(i,j,bi,bj)
217 & +aWght*tauy1(i,j,bi,bj))
218 Qnet(i,j,bi,bj) = bWght*Qnet0(i,j,bi,bj)
219 & +aWght*Qnet1(i,j,bi,bj)
220 EmPmR(i,j,bi,bj) = bWght*EmPmR0(i,j,bi,bj)
221 & +aWght*EmPmR1(i,j,bi,bj)
222 #ifdef SHORTWAVE_HEATING
223 Qsw(i,j,bi,bj) = bWght*Qsw0(i,j,bi,bj)
224 & +aWght*Qsw1(i,j,bi,bj)
225 #endif
226 ENDDO
227 ENDDO
228 ENDDO
229 ENDDO
230
231 C-- Diagnostics
232 cph IF (myThid.EQ.1 .AND. myTime.LT.62208000.) THEN
233 cph write(*,'(a,1p7e12.4,2i6,2e12.4)')
234 cph & 'time,SST,SSS,fu,fv,Q,E-P,i0,i1,a,b = ',
235 cph & myTime,
236 cph & SST(1,sNy,1,1),SSS(1,sNy,1,1),
237 cph & fu(1,sNy,1,1),fv(1,sNy,1,1),
238 cph & Qnet(1,sNy,1,1),EmPmR(1,sNy,1,1),
239 cph & intime0,intime1,aWght,bWght
240 cph write(*,'(a,1p7e12.4)')
241 cph & 'time,fu0,fu1,fu = ',
242 cph & myTime,
243 cph & taux0(1,sNy,1,1),taux1(1,sNy,1,1),fu(1,sNy,1,1),
244 cph & aWght,bWght
245 cph ENDIF
246
247 C endif for periodicForcing
248 ENDIF
249
250 #endif /* ALLOW_EXF */
251
252 RETURN
253 END
254
255 CBOP
256 C !ROUTINE: LEF_ZERO
257 C !INTERFACE:
258 SUBROUTINE LEF_ZERO( arr ,myThid )
259 C !DESCRIPTION: \bv
260 C This routine simply sets the argument array to zero
261 C Used only by EXTERNAL_FIELDS_LOAD
262 C \ev
263 C !USES:
264 IMPLICIT NONE
265 C === Global variables ===
266 #include "SIZE.h"
267 #include "EEPARAMS.h"
268 C !INPUT/OUTPUT PARAMETERS:
269 C === Arguments ===
270 _RS arr (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
271 INTEGER myThid
272 C !LOCAL VARIABLES:
273 C === Local variables ===
274 INTEGER i,j,bi,bj
275 CEOP
276
277 DO bj = myByLo(myThid), myByHi(myThid)
278 DO bi = myBxLo(myThid), myBxHi(myThid)
279 DO j=1-Oly,sNy+Oly
280 DO i=1-Olx,sNx+Olx
281 arr(i,j,bi,bj)=0.
282 ENDDO
283 ENDDO
284 ENDDO
285 ENDDO
286
287 RETURN
288 END

  ViewVC Help
Powered by ViewVC 1.1.22