/[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.9 - (show annotations) (download)
Fri Feb 8 22:22:06 2002 UTC (22 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint44e_post, checkpoint44f_post, chkpt44d_post, checkpoint44e_pre, checkpoint44h_pre, checkpoint45a_post, checkpoint44g_post, checkpoint45b_post, release1_final_v1, checkpoint45c_post, checkpoint44h_post, checkpoint45, chkpt44c_post, checkpoint44f_pre
Branch point for: release1_final
Changes since 1.8: +3 -5 lines
read the appropriate EmPmR record when using periodicExternalForcing

1 C $Header: /u/gcmpack/MITgcm/model/src/external_fields_load.F,v 1.8 2001/09/26 18:09:14 cnh Exp $
2 C $Name: $
3
4 #include "CPP_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: EXTERNAL_FIELDS_LOAD
8 C !INTERFACE:
9 SUBROUTINE EXTERNAL_FIELDS_LOAD( myTime, myIter, myThid )
10 C !DESCRIPTION: \bv
11 C *==========================================================*
12 C | SUBROUTINE EXTERNAL_FIELDS_LOAD
13 C | o Control reading of fields from external source.
14 C *==========================================================*
15 C | External source field loading routine.
16 C | This routine is called every time we want to
17 C | load a a set of external fields. The routine decides
18 C | which fields to load and then reads them in.
19 C | This routine needs to be customised for particular
20 C | experiments.
21 C | Notes
22 C | =====
23 C | Two-dimensional and three-dimensional I/O are handled in
24 C | the following way under MITgcmUV. A master thread
25 C | performs I/O using system calls. This threads reads data
26 C | into a temporary buffer. At present the buffer is loaded
27 C | with the entire model domain. This is probably OK for now
28 C | Each thread then copies data from the buffer to the
29 C | region of the proper array it is responsible for.
30 C | =====
31 C | Conversion of flux fields are described in FFIELDS.h
32 C *==========================================================*
33 C \ev
34
35 C !USES:
36 IMPLICIT NONE
37 C === Global variables ===
38 #include "SIZE.h"
39 #include "EEPARAMS.h"
40 #include "PARAMS.h"
41 #include "FFIELDS.h"
42 #include "GRID.h"
43 #include "DYNVARS.h"
44 LOGICAL DIFFERENT_MULTIPLE
45 EXTERNAL DIFFERENT_MULTIPLE
46
47 C !INPUT/OUTPUT PARAMETERS:
48 C === Routine arguments ===
49 C myThid - Thread no. that called this routine.
50 C myTime - Simulation time
51 C myIter - Simulation timestep number
52 INTEGER myThid
53 _RL myTime
54 INTEGER myIter
55
56
57 C !LOCAL VARIABLES:
58 C === Local arrays ===
59 C taux[01] :: Temp. for zonal wind stress
60 C tauy[01] :: Temp. for merid. wind stress
61 C qnet[01] :: Temp. for heat flux
62 C empmr[01] :: Temp. for fresh water flux
63 C sst[01] :: Temp. for theta climatalogy
64 C sss[01] :: Temp. for theta climatalogy
65 C qsw[01] :: Temp. for short wave component of heat flux
66 C [01] :: End points for interpolation
67 C Above use static heap storage to allow exchange.
68 C aWght, bWght :: Interpolation weights
69 COMMON /TDFIELDS/
70 & taux0, tauy0, Qnet0, EmPmR0, SST0, SSS0, Qsw0,
71 & taux1, tauy1, Qnet1, EmPmR1, SST1, SSS1, Qsw1
72 _RS taux0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
73 _RS tauy0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
74 _RS Qnet0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
75 _RS EmPmR0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
76 _RS SST0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
77 _RS SSS0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
78 _RS Qsw0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
79 _RS taux1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
80 _RS tauy1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
81 _RS Qnet1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
82 _RS EmPmR1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
83 _RS SST1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
84 _RS SSS1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
85 _RS Qsw1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
86 INTEGER bi,bj,i,j,intime0,intime1
87 _RL aWght,bWght,rdt
88 INTEGER nForcingPeriods,Imytm,Ifprd,Ifcyc,Iftm
89 CEOP
90
91 IF ( periodicExternalForcing ) THEN
92
93 C First call requires that we initialize everything to zero for safety
94 IF ( myIter .EQ. nIter0 ) THEN
95 CALL LEF_ZERO( taux0 ,myThid )
96 CALL LEF_ZERO( tauy0 ,myThid )
97 CALL LEF_ZERO( Qnet0 ,myThid )
98 CALL LEF_ZERO( EmPmR0 ,myThid )
99 CALL LEF_ZERO( SST0 ,myThid )
100 CALL LEF_ZERO( SSS0 ,myThid )
101 CALL LEF_ZERO( Qsw0 ,myThid )
102 CALL LEF_ZERO( taux1 ,myThid )
103 CALL LEF_ZERO( tauy1 ,myThid )
104 CALL LEF_ZERO( Qnet1 ,myThid )
105 CALL LEF_ZERO( EmPmR1 ,myThid )
106 CALL LEF_ZERO( SST1 ,myThid )
107 CALL LEF_ZERO( SSS1 ,myThid )
108 CALL LEF_ZERO( Qsw1 ,myThid )
109 ENDIF
110
111 C Now calculate whether it is time to update the forcing arrays
112 rdt=1. _d 0 / deltaTclock
113 nForcingPeriods=int(externForcingCycle/externForcingPeriod+0.5)
114 Imytm=int(myTime*rdt+0.5)
115 Ifprd=int(externForcingPeriod*rdt+0.5)
116 Ifcyc=int(externForcingCycle*rdt+0.5)
117 Iftm=mod( Imytm+Ifcyc-Ifprd/2 ,Ifcyc)
118
119 intime0=int(Iftm/Ifprd)
120 intime1=mod(intime0+1,nForcingPeriods)
121 aWght=float( Iftm-Ifprd*intime0 )/float( Ifprd )
122 bWght=1.-aWght
123
124 intime0=intime0+1
125 intime1=intime1+1
126
127 IF (
128 & Iftm-Ifprd*(intime0-1) .EQ. 0
129 & .OR. myIter .EQ. nIter0
130 & ) THEN
131
132 _BEGIN_MASTER(myThid)
133
134 C If the above condition is met then we need to read in
135 C data for the period ahead and the period behind myTime.
136 WRITE(*,*)
137 & 'S/R EXTERNAL_FIELDS_LOAD: Reading new data',myTime,myIter
138
139 IF ( zonalWindFile .NE. ' ' ) THEN
140 CALL READ_REC_XY_RS( zonalWindFile,taux0,intime0,myIter,myThid )
141 CALL READ_REC_XY_RS( zonalWindFile,taux1,intime1,myIter,myThid )
142 ENDIF
143 IF ( meridWindFile .NE. ' ' ) THEN
144 CALL READ_REC_XY_RS( meridWindFile,tauy0,intime0,myIter,myThid )
145 CALL READ_REC_XY_RS( meridWindFile,tauy1,intime1,myIter,myThid )
146 ENDIF
147 IF ( surfQFile .NE. ' ' ) THEN
148 CALL READ_REC_XY_RS( surfQFile,Qnet0,intime0,myIter,myThid )
149 CALL READ_REC_XY_RS( surfQFile,Qnet1,intime1,myIter,myThid )
150 ENDIF
151 IF ( EmPmRfile .NE. ' ' ) THEN
152 CALL READ_REC_XY_RS( EmPmRfile,EmPmR0,intime0,myIter,myThid )
153 CALL READ_REC_XY_RS( EmPmRfile,EmPmR1,intime1,myIter,myThid )
154 ENDIF
155 IF ( thetaClimFile .NE. ' ' ) THEN
156 CALL READ_REC_XY_RS( thetaClimFile,SST0,intime0,myIter,myThid )
157 CALL READ_REC_XY_RS( thetaClimFile,SST1,intime1,myIter,myThid )
158 ENDIF
159 IF ( saltClimFile .NE. ' ' ) THEN
160 CALL READ_REC_XY_RS( saltClimFile,SSS0,intime0,myIter,myThid )
161 CALL READ_REC_XY_RS( saltClimFile,SSS1,intime1,myIter,myThid )
162 ENDIF
163 #ifdef SHORTWAVE_HEATING
164 IF ( surfQswFile .NE. ' ' ) THEN
165 CALL READ_REC_XY_RS( surfQswFile,Qsw0,intime0,myIter,myThid )
166 CALL READ_REC_XY_RS( surfQswFile,Qsw1,intime1,myIter,myThid )
167 ENDIF
168 #endif
169
170 _END_MASTER(myThid)
171 C
172 _EXCH_XY_R4(SST0 , myThid )
173 _EXCH_XY_R4(SST1 , myThid )
174 _EXCH_XY_R4(SSS0 , myThid )
175 _EXCH_XY_R4(SSS1 , myThid )
176 _EXCH_XY_R4(taux0 , myThid )
177 _EXCH_XY_R4(taux1 , myThid )
178 _EXCH_XY_R4(tauy0 , myThid )
179 _EXCH_XY_R4(tauy1 , myThid )
180 _EXCH_XY_R4(Qnet0, myThid )
181 _EXCH_XY_R4(Qnet1, myThid )
182 _EXCH_XY_R4(EmPmR0, myThid )
183 _EXCH_XY_R4(EmPmR1, myThid )
184 #ifdef SHORTWAVE_HEATING
185 _EXCH_XY_R4(Qsw0, myThid )
186 _EXCH_XY_R4(Qsw1, myThid )
187 #endif
188 C
189 ENDIF
190
191 C-- Interpolate fu,fv,Qnet,EmPmR,SST,SSS,Qsw
192 DO bj = myByLo(myThid), myByHi(myThid)
193 DO bi = myBxLo(myThid), myBxHi(myThid)
194 DO j=1-Oly,sNy+Oly
195 DO i=1-Olx,sNx+Olx
196 SST(i,j,bi,bj) = bWght*SST0(i,j,bi,bj)
197 & +aWght*SST1(i,j,bi,bj)
198 SSS(i,j,bi,bj) = bWght*SSS0(i,j,bi,bj)
199 & +aWght*SSS1(i,j,bi,bj)
200 fu(i,j,bi,bj) = bWght*taux0(i,j,bi,bj)
201 & +aWght*taux1(i,j,bi,bj)
202 fv(i,j,bi,bj) = bWght*tauy0(i,j,bi,bj)
203 & +aWght*tauy1(i,j,bi,bj)
204 Qnet(i,j,bi,bj) = bWght*Qnet0(i,j,bi,bj)
205 & +aWght*Qnet1(i,j,bi,bj)
206 EmPmR(i,j,bi,bj) = bWght*EmPmR0(i,j,bi,bj)
207 & +aWght*EmPmR1(i,j,bi,bj)
208 #ifdef SHORTWAVE_HEATING
209 Qsw(i,j,bi,bj) = bWght*Qsw0(i,j,bi,bj)
210 & +aWght*Qsw1(i,j,bi,bj)
211 #endif
212 ENDDO
213 ENDDO
214 ENDDO
215 ENDDO
216
217 C-- Diagnostics
218 IF (myThid.EQ.1 .AND. myTime.LT.62208000.) THEN
219 write(*,'(a,1p7e12.4,2i6,2e12.4)')
220 & 'time,SST,SSS,fu,fv,Q,E-P,i0,i1,a,b = ',
221 & myTime,
222 & SST(1,sNy,1,1),SSS(1,sNy,1,1),
223 & fu(1,sNy,1,1),fv(1,sNy,1,1),
224 & Qnet(1,sNy,1,1),EmPmR(1,sNy,1,1),
225 & intime0,intime1,aWght,bWght
226 write(*,'(a,1p7e12.4)')
227 & 'time,fu0,fu1,fu = ',
228 & myTime,
229 & taux0(1,sNy,1,1),taux1(1,sNy,1,1),fu(1,sNy,1,1),
230 & aWght,bWght
231 ENDIF
232
233 C endif for periodicForcing
234 ENDIF
235
236 RETURN
237 END
238
239 CBOP
240 C !ROUTINE: LEF_ZERO
241 C !INTERFACE:
242 SUBROUTINE LEF_ZERO( arr ,myThid )
243 C !DESCRIPTION: \bv
244 C This routine simply sets the argument array to zero
245 C Used only by EXTERNAL_FIELDS_LOAD
246 C \ev
247 C !USES:
248 IMPLICIT NONE
249 C === Global variables ===
250 #include "SIZE.h"
251 #include "EEPARAMS.h"
252 C !INPUT/OUTPUT PARAMETERS:
253 C === Arguments ===
254 _RS arr (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
255 INTEGER myThid
256 C !LOCAL VARIABLES:
257 C === Local variables ===
258 INTEGER i,j,bi,bj
259 CEOP
260
261 DO bj = myByLo(myThid), myByHi(myThid)
262 DO bi = myBxLo(myThid), myBxHi(myThid)
263 DO j=1-Oly,sNy+Oly
264 DO i=1-Olx,sNx+Olx
265 arr(i,j,bi,bj)=0.
266 ENDDO
267 ENDDO
268 ENDDO
269 ENDDO
270
271 RETURN
272 END

  ViewVC Help
Powered by ViewVC 1.1.22