/[MITgcm]/MITgcm/pkg/dic/dic_fields_load.F
ViewVC logotype

Contents of /MITgcm/pkg/dic/dic_fields_load.F

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


Revision 1.30 - (show annotations) (download)
Sun Apr 17 21:08:40 2011 UTC (13 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62w, checkpoint62y, checkpoint62x
Changes since 1.29: +68 -36 lines
- call S/R GET_PERIODIC_INTERVAL to get interp. weights and time reccord number;
- apply EXCH to temp arrays [0,1] after loading in dic_fields_load.F

1 C $Header: /u/gcmpack/MITgcm/pkg/dic/dic_fields_load.F,v 1.29 2010/04/11 22:03:53 jmc Exp $
2 C $Name: $
3
4 #include "DIC_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: DIC_FIELDS_LOAD
8
9 C !INTERFACE: ==========================================================
10 SUBROUTINE DIC_FIELDS_LOAD (
11 I myIter,myTime,myThid)
12
13 C !DESCRIPTION:
14 C Read in fields needed for CO2,O2 fluxterms, silica for pH calculation
15
16 C !USES: ===============================================================
17 IMPLICIT NONE
18 #include "SIZE.h"
19 #include "EEPARAMS.h"
20 #include "PARAMS.h"
21 #include "GRID.h"
22 #include "DIC_VARS.h"
23 #include "DIC_LOAD.h"
24 #ifdef ALLOW_THSICE
25 #include "THSICE_VARS.h"
26 #endif
27 #ifdef ALLOW_SEAICE
28 #include "SEAICE.h"
29 #endif
30
31 C !INPUT PARAMETERS: ===================================================
32 C myThid :: thread number
33 C myIter :: current timestep
34 C myTime :: current time
35 INTEGER myIter
36 _RL myTime
37 INTEGER myThid
38
39 #ifdef ALLOW_DIC
40
41 c !LOCAL VARIABLES: ===================================================
42 INTEGER bi, bj, i, j
43 INTEGER intimeP, intime0, intime1
44 _RL aWght,bWght
45 #ifdef READ_PAR
46 CHARACTER*(MAX_LEN_MBUF) msgBuf
47 #endif
48 CEOP
49
50 IF ( DIC_forcingCycle.gt.0. _d 0 ) THEN
51
52 C-- Now calculate whether it is time to update the forcing arrays
53 CALL GET_PERIODIC_INTERVAL(
54 O intimeP, intime0, intime1, bWght, aWght,
55 I DIC_forcingCycle, DIC_forcingPeriod,
56 I deltaTclock, myTime, myThid )
57
58 bi = myBxLo(myThid)
59 bj = myByLo(myThid)
60 #ifdef ALLOW_DEBUG
61 IF ( debugLevel.GE.debLevA ) THEN
62 _BEGIN_MASTER(myThid)
63 WRITE(standardMessageUnit,'(A,I10,A,4I5,A,2F14.10)')
64 & ' DIC_FIELDS_LOAD,', myIter,
65 & ' : iP,iLd,i0,i1=', intimeP,DIC_ldRec(bi,bj), intime0,intime1,
66 & ' ; Wght=', bWght, aWght
67 _END_MASTER(myThid)
68 ENDIF
69 #endif /* ALLOW_DEBUG */
70
71 #ifdef ALLOW_AUTODIFF_TAMC
72 C- assuming that we call S/R DIC_FIELDS_LOAD at each time-step and
73 C with increasing time, this will catch when we need to load new records;
74 C But with Adjoint run, this is not always the case => might end-up using
75 C the wrong time-records
76 IF ( intime0.NE.intimeP .OR. myIter.EQ.nIter0 ) THEN
77 #else /* ALLOW_AUTODIFF_TAMC */
78 C- Make no assumption on sequence of calls to DIC_FIELDS_LOAD ;
79 C This is the correct formulation (works in Adjoint run).
80 C Unfortunatly, produces many recomputations <== not used until it is fixed
81 IF ( intime1.NE.DIC_ldRec(bi,bj) ) THEN
82 #endif /* ALLOW_AUTODIFF_TAMC */
83
84 C-- If the above condition is met then we need to read in
85 C data for the period ahead and the period behind myTime.
86 _BEGIN_MASTER(myThid)
87 WRITE(standardMessageUnit,'(A,I10,A,2(2I5,A))')
88 & ' DIC_FIELDS_LOAD, it=', myIter,
89 & ' : Reading new data, i0,i1=', intime0, intime1,
90 & ' (prev=', intimeP, DIC_ldRec(bi,bj), ' )'
91 _END_MASTER(myThid)
92
93 _BARRIER
94
95 IF ( DIC_windFile .NE. ' ' ) THEN
96 CALL READ_REC_XY_RS( DIC_windFile,dicwind0,intime0,
97 & myIter,myThid )
98 CALL READ_REC_XY_RS( DIC_windFile,dicwind1,intime1,
99 & myIter,myThid )
100 ENDIF
101 IF ( DIC_atmospFile .NE. ' ' ) THEN
102 CALL READ_REC_XY_RS( DIC_atmospFile,atmosp0,intime0,
103 & myIter,myThid )
104 CALL READ_REC_XY_RS( DIC_atmospFile,atmosp1,intime1,
105 & myIter,myThid )
106 ENDIF
107 IF ( DIC_silicaFile .NE. ' ' ) THEN
108 CALL READ_REC_XY_RS( DIC_silicaFile,silica0,intime0,
109 & myIter,myThid )
110 CALL READ_REC_XY_RS( DIC_silicaFile,silica1,intime1,
111 & myIter,myThid )
112 ENDIF
113 IF ( DIC_iceFile .NE. ' ' ) THEN
114 CALL READ_REC_XY_RS( DIC_iceFile,ice0,intime0,
115 & myIter,myThid )
116 CALL READ_REC_XY_RS( DIC_iceFile,ice1,intime1,
117 & myIter,myThid )
118 ENDIF
119 #ifdef READ_PAR
120 IF ( Filename1 .NE. ' ' ) THEN
121 CALL READ_REC_XY_RS( Filename1,par0,intime0,
122 & myIter,myThid )
123 CALL READ_REC_XY_RS( Filename1,par1,intime1,
124 & myIter,myThid )
125 ENDIF
126 #endif
127 #ifdef ALLOW_FE
128 IF ( DIC_ironFile .NE. ' ' ) THEN
129 CALL READ_REC_XY_RS( DIC_ironFile,feinput0,intime0,
130 & myIter,myThid )
131 CALL READ_REC_XY_RS( DIC_ironFile,feinput1,intime1,
132 & myIter,myThid )
133 ENDIF
134 #endif
135
136 C-- fill-in overlap after loading temp arrays:
137 _EXCH_XY_RS(dicwind0, myThid )
138 _EXCH_XY_RS(dicwind1, myThid )
139 _EXCH_XY_RS(atmosp0, myThid )
140 _EXCH_XY_RS(atmosp1, myThid )
141 _EXCH_XY_RS(silica0, myThid )
142 _EXCH_XY_RS(silica1, myThid )
143 _EXCH_XY_RS(ice0, myThid )
144 _EXCH_XY_RS(ice1, myThid )
145 #ifdef READ_PAR
146 _EXCH_XY_RS(par0, myThid )
147 _EXCH_XY_RS(par1, myThid )
148 #endif
149 #ifdef ALLOW_FE
150 _EXCH_XY_RS(feinput0, myThid )
151 _EXCH_XY_RS(feinput1, myThid )
152 #endif
153
154 C- save newly loaded time-record
155 DO bj = myByLo(myThid), myByHi(myThid)
156 DO bi = myBxLo(myThid), myBxHi(myThid)
157 DIC_ldRec(bi,bj) = intime1
158 ENDDO
159 ENDDO
160
161 C- end if-bloc (time to load new fields)
162 ENDIF
163
164 DO bj = myByLo(myThid), myByHi(myThid)
165 DO bi = myBxLo(myThid), myBxHi(myThid)
166 IF ( DIC_windFile .NE. ' ' ) THEN
167 DO j=1-Oly,sNy+Oly
168 DO i=1-Olx,sNx+Olx
169 WIND(i,j,bi,bj) = bWght*dicwind0(i,j,bi,bj)
170 & + aWght*dicwind1(i,j,bi,bj)
171 ENDDO
172 ENDDO
173 C calculate piston velocity
174 C QQ: note - we should have wind speed variance in here
175 C QQ also need to check units, and conversion factors
176 c pisvel(i,j,bi,bj) =0.337*wind(i,j,bi,bj)**2/3.6d5 !QQQQ
177 ENDIF
178 #ifndef USE_PLOAD
179 IF ( DIC_atmospFile .NE. ' ' ) THEN
180 DO j=1-Oly,sNy+Oly
181 DO i=1-Olx,sNx+Olx
182 AtmosP(i,j,bi,bj) = bWght*atmosp0(i,j,bi,bj)
183 & + aWght*atmosp1(i,j,bi,bj)
184 ENDDO
185 ENDDO
186 ENDIF
187 #endif
188 IF ( DIC_silicaFile .NE. ' ' ) THEN
189 DO j=1-Oly,sNy+Oly
190 DO i=1-Olx,sNx+Olx
191 SILICA(i,j,bi,bj) = bWght*silica0(i,j,bi,bj)
192 & + aWght*silica1(i,j,bi,bj)
193 ENDDO
194 ENDDO
195 ENDIF
196 IF ( DIC_iceFile .NE. ' ' ) THEN
197 DO j=1-Oly,sNy+Oly
198 DO i=1-Olx,sNx+Olx
199 FIce(i,j,bi,bj) = bWght*ice0(i,j,bi,bj)
200 & + aWght*ice1(i,j,bi,bj)
201 ENDDO
202 ENDDO
203 ENDIF
204
205 #ifdef READ_PAR
206 IF ( Filename1 .NE. ' ' ) THEN
207 DO j=1-Oly,sNy+Oly
208 DO i=1-Olx,sNx+Olx
209 PAR(i,j,bi,bj) = bWght*par0(i,j,bi,bj)
210 & + aWght*par1(i,j,bi,bj)
211 ENDDO
212 ENDDO
213 ELSE
214 WRITE(msgBuf,'(2A)')
215 & ' DIC_FIELDS_LOAD: You need to provide ',
216 & ' a file if you want to use READ_PAR'
217 CALL PRINT_ERROR( msgBuf, myThid )
218 STOP 'ABNORMAL END: S/R DIC_FIELDS_LOAD'
219 ENDIF
220 #endif
221 #ifdef ALLOW_FE
222 IF ( DIC_ironFile .NE. ' ' ) THEN
223 DO j=1-Oly,sNy+Oly
224 DO i=1-Olx,sNx+Olx
225 InputFe(i,j,bi,bj) = bWght*feinput0(i,j,bi,bj)
226 & + aWght*feinput1(i,j,bi,bj)
227 ENDDO
228 ENDDO
229 ENDIF
230 #endif
231 ENDDO
232 ENDDO
233
234 C endif for DIC_forcingCycle
235 ENDIF
236
237 DO bj = myByLo(myThid), myByHi(myThid)
238 DO bi = myBxLo(myThid), myBxHi(myThid)
239 #ifdef ALLOW_SEAICE
240 IF ( useSEAICE ) THEN
241 DO j=1-Oly,sNy+Oly
242 DO i=1-Olx,sNx+Olx
243 FIce(i,j,bi,bj) = AREA(i,j,bi,bj)
244 ENDDO
245 ENDDO
246 ENDIF
247 #endif
248 #ifdef ALLOW_THSICE
249 IF ( useThSIce ) THEN
250 DO j=1-Oly,sNy+Oly
251 DO i=1-Olx,sNx+Olx
252 FIce(i,j,bi,bj) = iceMask(i,j,bi,bj)
253 ENDDO
254 ENDDO
255 ENDIF
256 #endif
257 ENDDO
258 ENDDO
259
260 #endif /* ALLOW_DIC */
261 RETURN
262 END

  ViewVC Help
Powered by ViewVC 1.1.22