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

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

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


Revision 1.8 - (hide annotations) (download)
Wed Sep 26 18:09:14 2001 UTC (22 years, 8 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint43a-release1mods, release1_b1, checkpoint43, icebear5, icebear4, icebear3, icebear2, release1-branch_tutorials, chkpt44a_post, chkpt44c_pre, ecco_c44_e19, ecco_c44_e18, ecco_c44_e17, ecco_c44_e16, release1-branch-end, checkpoint44b_post, ecco_ice2, ecco_ice1, ecco_c44_e22, ecco_c44_e25, chkpt44a_pre, ecco_c44_e23, ecco_c44_e20, ecco_c44_e21, ecco_c44_e26, ecco_c44_e27, ecco_c44_e24, ecco-branch-mod1, ecco-branch-mod2, ecco-branch-mod3, ecco-branch-mod4, ecco-branch-mod5, release1_beta1, checkpoint44b_pre, checkpoint42, checkpoint41, checkpoint44, release1-branch_branchpoint
Branch point for: c24_e25_ice, release1-branch, release1, ecco-branch, icebear, release1_coupled
Changes since 1.7: +54 -32 lines
Bringing comments up to data and formatting for document extraction.

1 cnh 1.8 C $Header: /u/gcmpack/models/MITgcmUV/model/src/external_fields_load.F,v 1.7 2001/05/29 14:01:37 adcroft Exp $
2 adcroft 1.7 C $Name: $
3 heimbach 1.1
4     #include "CPP_OPTIONS.h"
5    
6 cnh 1.8 CBOP
7     C !ROUTINE: EXTERNAL_FIELDS_LOAD
8     C !INTERFACE:
9 heimbach 1.1 SUBROUTINE EXTERNAL_FIELDS_LOAD( myTime, myIter, myThid )
10 cnh 1.8 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 heimbach 1.1 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 heimbach 1.3 #include "DYNVARS.h"
44 cnh 1.8 LOGICAL DIFFERENT_MULTIPLE
45     EXTERNAL DIFFERENT_MULTIPLE
46 heimbach 1.1
47 cnh 1.8 C !INPUT/OUTPUT PARAMETERS:
48 heimbach 1.1 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 cnh 1.8 C !LOCAL VARIABLES:
58 heimbach 1.1 C === Local arrays ===
59 cnh 1.8 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 heimbach 1.1 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 cnh 1.8 CEOP
90 heimbach 1.1
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 adcroft 1.7 WRITE(*,*)
137     & 'S/R EXTERNAL_FIELDS_LOAD: Reading new data',myTime,myIter
138 heimbach 1.1
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 heimbach 1.3 Cfixed CALL READ_REC_XY_RS( EmPmRfile,EmPmR0,intime0,myIter,myThid )
153     Cfixed CALL READ_REC_XY_RS( EmPmRfile,EmPmR1,intime1,myIter,myThid )
154     CALL READ_REC_XY_RS( EmPmRfile,EmPmR0,1,myIter,myThid )
155     CALL READ_REC_XY_RS( EmPmRfile,EmPmR1,1,myIter,myThid )
156 heimbach 1.1 ENDIF
157     IF ( thetaClimFile .NE. ' ' ) THEN
158     CALL READ_REC_XY_RS( thetaClimFile,SST0,intime0,myIter,myThid )
159     CALL READ_REC_XY_RS( thetaClimFile,SST1,intime1,myIter,myThid )
160     ENDIF
161     IF ( saltClimFile .NE. ' ' ) THEN
162     CALL READ_REC_XY_RS( saltClimFile,SSS0,intime0,myIter,myThid )
163     CALL READ_REC_XY_RS( saltClimFile,SSS1,intime1,myIter,myThid )
164     ENDIF
165     #ifdef SHORTWAVE_HEATING
166     IF ( surfQswFile .NE. ' ' ) THEN
167     CALL READ_REC_XY_RS( surfQswFile,Qsw0,intime0,myIter,myThid )
168     CALL READ_REC_XY_RS( surfQswFile,Qsw1,intime1,myIter,myThid )
169     ENDIF
170     #endif
171    
172     _END_MASTER(myThid)
173     C
174     _EXCH_XY_R4(SST0 , myThid )
175     _EXCH_XY_R4(SST1 , myThid )
176     _EXCH_XY_R4(SSS0 , myThid )
177     _EXCH_XY_R4(SSS1 , myThid )
178     _EXCH_XY_R4(taux0 , myThid )
179     _EXCH_XY_R4(taux1 , myThid )
180     _EXCH_XY_R4(tauy0 , myThid )
181     _EXCH_XY_R4(tauy1 , myThid )
182     _EXCH_XY_R4(Qnet0, myThid )
183     _EXCH_XY_R4(Qnet1, myThid )
184     _EXCH_XY_R4(EmPmR0, myThid )
185     _EXCH_XY_R4(EmPmR1, myThid )
186     #ifdef SHORTWAVE_HEATING
187     _EXCH_XY_R4(Qsw0, myThid )
188     _EXCH_XY_R4(Qsw1, myThid )
189     #endif
190     C
191     ENDIF
192    
193     C-- Interpolate fu,fv,Qnet,EmPmR,SST,SSS,Qsw
194     DO bj = myByLo(myThid), myByHi(myThid)
195     DO bi = myBxLo(myThid), myBxHi(myThid)
196     DO j=1-Oly,sNy+Oly
197     DO i=1-Olx,sNx+Olx
198     SST(i,j,bi,bj) = bWght*SST0(i,j,bi,bj)
199     & +aWght*SST1(i,j,bi,bj)
200     SSS(i,j,bi,bj) = bWght*SSS0(i,j,bi,bj)
201     & +aWght*SSS1(i,j,bi,bj)
202     fu(i,j,bi,bj) = bWght*taux0(i,j,bi,bj)
203     & +aWght*taux1(i,j,bi,bj)
204     fv(i,j,bi,bj) = bWght*tauy0(i,j,bi,bj)
205     & +aWght*tauy1(i,j,bi,bj)
206     Qnet(i,j,bi,bj) = bWght*Qnet0(i,j,bi,bj)
207     & +aWght*Qnet1(i,j,bi,bj)
208     EmPmR(i,j,bi,bj) = bWght*EmPmR0(i,j,bi,bj)
209     & +aWght*EmPmR1(i,j,bi,bj)
210     #ifdef SHORTWAVE_HEATING
211     Qsw(i,j,bi,bj) = bWght*Qsw0(i,j,bi,bj)
212     & +aWght*Qsw1(i,j,bi,bj)
213     #endif
214     ENDDO
215     ENDDO
216     ENDDO
217     ENDDO
218 heimbach 1.3
219     C-- Diagnostics
220     IF (myThid.EQ.1 .AND. myTime.LT.62208000.) THEN
221 heimbach 1.6 write(*,'(a,1p7e12.4,2i6,2e12.4)')
222 heimbach 1.3 & 'time,SST,SSS,fu,fv,Q,E-P,i0,i1,a,b = ',
223     & myTime,
224     & SST(1,sNy,1,1),SSS(1,sNy,1,1),
225     & fu(1,sNy,1,1),fv(1,sNy,1,1),
226     & Qnet(1,sNy,1,1),EmPmR(1,sNy,1,1),
227     & intime0,intime1,aWght,bWght
228 heimbach 1.6 write(*,'(a,1p7e12.4)')
229 heimbach 1.3 & 'time,fu0,fu1,fu = ',
230     & myTime,
231     & taux0(1,sNy,1,1),taux1(1,sNy,1,1),fu(1,sNy,1,1),
232     & aWght,bWght
233     ENDIF
234 heimbach 1.1
235     C endif for periodicForcing
236     ENDIF
237    
238     RETURN
239     END
240    
241 cnh 1.8 CBOP
242     C !ROUTINE: LEF_ZERO
243     C !INTERFACE:
244 heimbach 1.1 SUBROUTINE LEF_ZERO( arr ,myThid )
245 cnh 1.8 C !DESCRIPTION: \bv
246 heimbach 1.1 C This routine simply sets the argument array to zero
247     C Used only by EXTERNAL_FIELDS_LOAD
248 cnh 1.8 C \ev
249     C !USES:
250 heimbach 1.1 IMPLICIT NONE
251     C === Global variables ===
252     #include "SIZE.h"
253     #include "EEPARAMS.h"
254 cnh 1.8 C !INPUT/OUTPUT PARAMETERS:
255 heimbach 1.1 C === Arguments ===
256     _RS arr (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
257     INTEGER myThid
258 cnh 1.8 C !LOCAL VARIABLES:
259 heimbach 1.1 C === Local variables ===
260     INTEGER i,j,bi,bj
261 cnh 1.8 CEOP
262 heimbach 1.1
263     DO bj = myByLo(myThid), myByHi(myThid)
264     DO bi = myBxLo(myThid), myBxHi(myThid)
265     DO j=1-Oly,sNy+Oly
266     DO i=1-Olx,sNx+Olx
267     arr(i,j,bi,bj)=0.
268     ENDDO
269     ENDDO
270     ENDDO
271     ENDDO
272    
273     RETURN
274     END

  ViewVC Help
Powered by ViewVC 1.1.22