/[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.33 - (show annotations) (download)
Fri Jun 8 20:31:10 2012 UTC (12 years ago) by stephd
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63o, checkpoint64, checkpoint65, checkpoint65b, checkpoint65c, checkpoint65a
Changes since 1.32: +5 -5 lines
o fix bug so #define READ_PAR will work

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

  ViewVC Help
Powered by ViewVC 1.1.22