/[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.11 - (show annotations) (download)
Thu May 19 21:46:15 2005 UTC (19 years ago) by ce107
Branch: MAIN
CVS Tags: checkpoint57t_post, checkpoint57m_post, checkpoint57v_post, checkpoint57s_post, checkpoint57j_post, checkpoint57y_post, checkpoint57x_post, checkpoint57y_pre, checkpoint57o_post, checkpoint57r_post, checkpoint57k_post, checkpoint57i_post, checkpoint58, checkpoint57w_post, checkpoint57p_post, checkpint57u_post, checkpoint57q_post, checkpoint57z_post, checkpoint57l_post
Changes since 1.10: +2 -2 lines
Minor fixes of datatypes, format descriptors, logical operators etc. to
get MITgcm to build and run successfully on AMD64 using GFortran (GCC 4.0.0).
Same changes would be necessary for other GFortran platforms.

Note: please use .NEQV. instead of the less portable .XOR. relational
operator that does not exist for F90/95.

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

  ViewVC Help
Powered by ViewVC 1.1.22