/[MITgcm]/MITgcm/pkg/autodiff/autodiff_store.F
ViewVC logotype

Annotation of /MITgcm/pkg/autodiff/autodiff_store.F

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


Revision 1.3 - (hide annotations) (download)
Wed Sep 26 04:12:40 2007 UTC (16 years, 9 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j
Changes since 1.2: +6 -1 lines
Include SEAICE_SALINITY in adjoint.

1 heimbach 1.3 C $Header: /u/gcmpack/MITgcm/pkg/autodiff/autodiff_store.F,v 1.2 2007/06/27 22:14:28 heimbach Exp $
2 heimbach 1.1 C $Name: $
3    
4     #include "PACKAGES_CONFIG.h"
5     #include "CPP_OPTIONS.h"
6     #ifdef ALLOW_OBCS
7     # include "OBCS_OPTIONS.h"
8     #endif
9     #ifdef ALLOW_SEAICE
10     # include "SEAICE_OPTIONS.h"
11     #endif
12    
13     subroutine autodiff_store( mythid )
14    
15     c ==================================================================
16     c SUBROUTINE autodiff_store
17     c ==================================================================
18     c
19     c packing for checkpoint storage
20     c
21     c started: Matt Mazloff mmazloff@mit.edu 03-May-2007
22     c
23     c ==================================================================
24     c SUBROUTINE autodiff_store
25     c ==================================================================
26    
27     implicit none
28    
29     c == global variables ==
30    
31     #include "SIZE.h"
32     #include "EEPARAMS.h"
33     #include "PARAMS.h"
34     c**************************************
35     #ifdef ALLOW_AUTODIFF_TAMC
36    
37     c These includes are needed for
38     c AD-checkpointing.
39     c They provide the fields to be stored.
40    
41     # include "GRID.h"
42     # include "DYNVARS.h"
43     # include "FFIELDS.h"
44     # include "SURFACE.h"
45     # include "AUTODIFF.h"
46    
47     # ifdef ALLOW_OBCS
48     # include "OBCS.h"
49     # endif
50     # ifdef ALLOW_EXF
51     # include "EXF_FIELDS.h"
52     # ifdef ALLOW_BULKFORMULAE
53     # include "EXF_CONSTANTS.h"
54     # endif
55     # endif /* ALLOW_EXF */
56     # ifdef ALLOW_SEAICE
57     # include "SEAICE.h"
58     # endif
59    
60     # include "ctrl.h"
61    
62     c == routine arguments ==
63     c note: under the multi-threaded model myiter and
64     c mytime are local variables passed around as routine
65     c arguments. Although this is fiddly it saves the need to
66     c impose additional synchronisation points when they are
67     c updated.
68     c mythid - thread number for this instance of the routine.
69     integer mythid
70    
71     c == local variables ==
72    
73     integer bi,bj
74     integer I,J,K
75    
76     c-- == end of interface ==
77    
78     #ifndef DISABLE_DEBUGMODE
79     IF ( debugLevel .GE. debLevB )
80     & CALL DEBUG_ENTER('AUTODIFF_STORE',myThid)
81     #endif
82    
83     C-- Over all tiles
84     DO bj = myByLo(myThid), myByHi(myThid)
85     DO bi = myBxLo(myThid), myBxHi(myThid)
86     C- 2D arrays
87     DO J=1-Oly,sNy+Oly
88     DO I=1-Olx,sNx+Olx
89     StoreDynVars2D(I,J,bi,bj,1) = etan(I,J,bi,bj)
90     StoreDynVars2D(I,J,bi,bj,2) = surfaceforcingTice(I,J,bi,bj)
91     StoreDynVars2D(I,J,bi,bj,3) = taux0(I,J,bi,bj)
92     StoreDynVars2D(I,J,bi,bj,4) = taux1(I,J,bi,bj)
93     StoreDynVars2D(I,J,bi,bj,5) = tauy0(I,J,bi,bj)
94     StoreDynVars2D(I,J,bi,bj,6) = tauy1(I,J,bi,bj)
95     StoreDynVars2D(I,J,bi,bj,7) = qnet0(I,J,bi,bj)
96     StoreDynVars2D(I,J,bi,bj,8) = qnet1(I,J,bi,bj)
97     StoreDynVars2D(I,J,bi,bj,9) = empmr0(I,J,bi,bj)
98     StoreDynVars2D(I,J,bi,bj,10) = empmr1(I,J,bi,bj)
99     StoreDynVars2D(I,J,bi,bj,11) = sst0(I,J,bi,bj)
100     StoreDynVars2D(I,J,bi,bj,12) = sst1(I,J,bi,bj)
101     StoreDynVars2D(I,J,bi,bj,13) = sss0(I,J,bi,bj)
102     StoreDynVars2D(I,J,bi,bj,14) = sss1(I,J,bi,bj)
103     StoreDynVars2D(I,J,bi,bj,15) = saltflux0(I,J,bi,bj)
104     StoreDynVars2D(I,J,bi,bj,16) = saltflux1(I,J,bi,bj)
105     #ifdef SHORTWAVE_HEATING
106     StoreDynVars2D(I,J,bi,bj,17) = qsw0(I,J,bi,bj)
107     StoreDynVars2D(I,J,bi,bj,18) = qsw1(I,J,bi,bj)
108     #else
109     StoreDynVars2D(I,J,bi,bj,17) = 0.
110     StoreDynVars2D(I,J,bi,bj,18) = 0.
111     #endif
112     #ifdef ATMOSPHERIC_LOADING
113     StoreDynVars2D(I,J,bi,bj,19) = pload0(I,J,bi,bj)
114     StoreDynVars2D(I,J,bi,bj,20) = pload1(I,J,bi,bj)
115     #else
116     StoreDynVars2D(I,J,bi,bj,19) = 0.
117     StoreDynVars2D(I,J,bi,bj,20) = 0.
118     #endif
119     #ifdef EXACT_CONSERV
120     StoreDynVars2D(I,J,bi,bj,21) = etaH(I,J,bi,bj)
121     StoreDynVars2D(I,J,bi,bj,22) = dEtaHdt(I,J,bi,bj)
122     StoreDynVars2D(I,J,bi,bj,23) = PmEpR(I,J,bi,bj)
123     #else
124     StoreDynVars2D(I,J,bi,bj,21) = 0.
125     StoreDynVars2D(I,J,bi,bj,22) = 0.
126     StoreDynVars2D(I,J,bi,bj,23) = 0.
127     #endif
128     ENDDO
129     ENDDO
130     C- 3D arrays
131     DO K=1,Nr
132     DO J=1-Oly,sNy+Oly
133     DO I=1-Olx,sNx+Olx
134     StoreDynVars3D(I,J,K,bi,bj,1) = gs(I,J,K,bi,bj)
135     StoreDynVars3D(I,J,K,bi,bj,2) = gt(I,J,K,bi,bj)
136     StoreDynVars3D(I,J,K,bi,bj,3) = gtnm1(I,J,K,bi,bj)
137     StoreDynVars3D(I,J,K,bi,bj,4) = gsnm1(I,J,K,bi,bj)
138     StoreDynVars3D(I,J,K,bi,bj,5) = gunm1(I,J,K,bi,bj)
139     StoreDynVars3D(I,J,K,bi,bj,6) = gvnm1(I,J,K,bi,bj)
140     StoreDynVars3D(I,J,K,bi,bj,7) = theta(I,J,K,bi,bj)
141     StoreDynVars3D(I,J,K,bi,bj,8) = salt(I,J,K,bi,bj)
142     StoreDynVars3D(I,J,K,bi,bj,9) = uvel(I,J,K,bi,bj)
143     StoreDynVars3D(I,J,K,bi,bj,10) = vvel(I,J,K,bi,bj)
144     StoreDynVars3D(I,J,K,bi,bj,11) = wvel(I,J,K,bi,bj)
145     StoreDynVars3D(I,J,K,bi,bj,12) = totphihyd(I,J,K,bi,bj)
146     ENDDO
147     ENDDO
148     ENDDO
149     ENDDO
150     ENDDO
151    
152     #ifdef ALLOW_EXF
153    
154     C-- Over all tiles
155     DO bj = myByLo(myThid), myByHi(myThid)
156     DO bi = myBxLo(myThid), myBxHi(myThid)
157     C- 2D arrays
158     DO J=1-Oly,sNy+Oly
159     DO I=1-Olx,sNx+Olx
160 heimbach 1.2 StoreEXF1(I,J,bi,bj,1) = hflux0(I,J,bi,bj)
161     StoreEXF1(I,J,bi,bj,2) = hflux1(I,J,bi,bj)
162     StoreEXF1(I,J,bi,bj,3) = sflux0(I,J,bi,bj)
163     StoreEXF1(I,J,bi,bj,4) = sflux1(I,J,bi,bj)
164     StoreEXF1(I,J,bi,bj,5) = ustress0(I,J,bi,bj)
165     StoreEXF1(I,J,bi,bj,6) = ustress1(I,J,bi,bj)
166     StoreEXF1(I,J,bi,bj,7) = vstress0(I,J,bi,bj)
167     StoreEXF1(I,J,bi,bj,8) = vstress1(I,J,bi,bj)
168     StoreEXF1(I,J,bi,bj,9) = wspeed0(I,J,bi,bj)
169     StoreEXF1(I,J,bi,bj,10) = wspeed1(I,J,bi,bj)
170     # ifdef SHORTWAVE_HEATING
171     StoreEXF1(I,J,bi,bj,11) = swflux0(I,J,bi,bj)
172     StoreEXF1(I,J,bi,bj,12) = swflux1(I,J,bi,bj)
173     # else
174     StoreEXF1(I,J,bi,bj,11) = 0.0
175     StoreEXF1(I,J,bi,bj,12) = 0.0
176     # endif
177     # ifdef ALLOW_RUNOFF
178     StoreEXF1(I,J,bi,bj,13) = runoff0(I,J,bi,bj)
179     StoreEXF1(I,J,bi,bj,14) = runoff1(I,J,bi,bj)
180     # else
181 heimbach 1.1 StoreEXF1(I,J,bi,bj,13) = 0.0
182     StoreEXF1(I,J,bi,bj,14) = 0.0
183 heimbach 1.2 # endif
184     # ifdef ATMOSPHERIC_LOADING
185     StoreEXF1(I,J,bi,bj,15) = apressure0(I,J,bi,bj)
186     StoreEXF1(I,J,bi,bj,16) = apressure1(I,J,bi,bj)
187     StoreEXF1(I,J,bi,bj,17) = siceload(I,J,bi,bj)
188     # else
189 heimbach 1.1 StoreEXF1(I,J,bi,bj,15) = 0.0
190     StoreEXF1(I,J,bi,bj,16) = 0.0
191 heimbach 1.2 StoreEXF1(I,J,bi,bj,17) = 0.0
192     # endif
193     # ifdef ALLOW_CLIMSSS_RELAXATION
194     StoreEXF1(I,J,bi,bj,18) = climsss0(I,J,bi,bj)
195     StoreEXF1(I,J,bi,bj,19) = climsss1(I,J,bi,bj)
196     # else
197     StoreEXF1(I,J,bi,bj,18) = 0.0
198     StoreEXF1(I,J,bi,bj,19) = 0.0
199     # endif
200     # ifdef ALLOW_CLIMSST_RELAXATION
201     StoreEXF1(I,J,bi,bj,20) = climsst0(I,J,bi,bj)
202     StoreEXF1(I,J,bi,bj,21) = climsst1(I,J,bi,bj)
203     # else
204     StoreEXF1(I,J,bi,bj,20) = 0.0
205     StoreEXF1(I,J,bi,bj,21) = 0.0
206     # endif
207 heimbach 1.1 enddo
208     enddo
209     enddo
210     enddo
211    
212 heimbach 1.2 # if (defined (ALLOW_ATM_TEMP) || defined (ALLOW_ATM_WIND))
213 heimbach 1.1 C-- Over all tiles
214     DO bj = myByLo(myThid), myByHi(myThid)
215     DO bi = myBxLo(myThid), myBxHi(myThid)
216     C- 2D arrays
217     DO J=1-Oly,sNy+Oly
218     DO I=1-Olx,sNx+Olx
219 heimbach 1.2 # ifdef ALLOW_ATM_TEMP
220 heimbach 1.1 StoreEXF2(I,J,bi,bj,1) = aqh0(I,J,bi,bj)
221     StoreEXF2(I,J,bi,bj,2) = aqh1(I,J,bi,bj)
222     StoreEXF2(I,J,bi,bj,3) = atemp0(I,J,bi,bj)
223     StoreEXF2(I,J,bi,bj,4) = atemp1(I,J,bi,bj)
224     StoreEXF2(I,J,bi,bj,5) = precip0(I,J,bi,bj)
225     StoreEXF2(I,J,bi,bj,6) = precip1(I,J,bi,bj)
226     StoreEXF2(I,J,bi,bj,7) = lwflux0(I,J,bi,bj)
227     StoreEXF2(I,J,bi,bj,8) = lwflux1(I,J,bi,bj)
228 heimbach 1.2 # ifdef EXF_READ_EVAP
229     StoreEXF2(I,J,bi,bj,9) = evap0(I,J,bi,bj)
230     StoreEXF2(I,J,bi,bj,10) = evap1(I,J,bi,bj)
231     # else
232     StoreEXF2(I,J,bi,bj,9) = evap(I,J,bi,bj)
233     StoreEXF2(I,J,bi,bj,10) = 0.0
234     # endif /* EXF_READ_EVAP */
235     # ifdef ALLOW_DOWNWARD_RADIATION
236     StoreEXF2(I,J,bi,bj,11) = swdown0(I,J,bi,bj)
237     StoreEXF2(I,J,bi,bj,12) = swdown1(I,J,bi,bj)
238     StoreEXF2(I,J,bi,bj,13) = lwdown0(I,J,bi,bj)
239     StoreEXF2(I,J,bi,bj,14) = lwdown1(I,J,bi,bj)
240     # else
241     StoreEXF2(I,J,bi,bj,11) = 0.0
242 heimbach 1.1 StoreEXF2(I,J,bi,bj,12) = 0.0
243     StoreEXF2(I,J,bi,bj,13) = 0.0
244     StoreEXF2(I,J,bi,bj,14) = 0.0
245 heimbach 1.2 # endif
246     # endif /* ALLOW_ATM_TEMP */
247     # ifdef ALLOW_ATM_WIND
248     StoreEXF2(I,J,bi,bj,15) = uwind0(I,J,bi,bj)
249     StoreEXF2(I,J,bi,bj,16) = uwind1(I,J,bi,bj)
250     StoreEXF2(I,J,bi,bj,17) = vwind0(I,J,bi,bj)
251     StoreEXF2(I,J,bi,bj,18) = vwind1(I,J,bi,bj)
252     # else /* ALLOW_ATM_WIND undef */
253 heimbach 1.1 StoreEXF2(I,J,bi,bj,15) = 0.0
254     StoreEXF2(I,J,bi,bj,16) = 0.0
255     StoreEXF2(I,J,bi,bj,17) = 0.0
256     StoreEXF2(I,J,bi,bj,18) = 0.0
257 heimbach 1.2 # endif /* ALLOW_ATM_WIND */
258 heimbach 1.1 enddo
259     enddo
260     enddo
261     enddo
262     # endif /* ALLOW_ATM_TEMP */
263    
264     C-- Over all tiles
265     DO bj = myByLo(myThid), myByHi(myThid)
266     DO bi = myBxLo(myThid), myBxHi(myThid)
267     C- 2D arrays
268     DO J=1-Oly,sNy+Oly
269     DO I=1-Olx,sNx+Olx
270     # ifdef ALLOW_UWIND_CONTROL
271     StoreCTRLS1(I,J,bi,bj,1) = xx_uwind0(I,J,bi,bj)
272     StoreCTRLS1(I,J,bi,bj,2) = xx_uwind1(I,J,bi,bj)
273     # else
274     StoreCTRLS1(I,J,bi,bj,1) = 0.0
275     StoreCTRLS1(I,J,bi,bj,2) = 0.0
276     # endif
277     # ifdef ALLOW_VWIND_CONTROL
278     StoreCTRLS1(I,J,bi,bj,3) = xx_vwind0(I,J,bi,bj)
279     StoreCTRLS1(I,J,bi,bj,4) = xx_vwind1(I,J,bi,bj)
280     # else
281     StoreCTRLS1(I,J,bi,bj,3) = 0.0
282     StoreCTRLS1(I,J,bi,bj,4) = 0.0
283     # endif
284     # ifdef ALLOW_ATEMP_CONTROL
285     StoreCTRLS1(I,J,bi,bj,5) = xx_atemp0(I,J,bi,bj)
286     StoreCTRLS1(I,J,bi,bj,6) = xx_atemp1(I,J,bi,bj)
287     # else
288     StoreCTRLS1(I,J,bi,bj,5) = 0.0
289     StoreCTRLS1(I,J,bi,bj,6) = 0.0
290     # endif
291     # ifdef ALLOW_AQH_CONTROL
292     StoreCTRLS1(I,J,bi,bj,7) = xx_aqh0(I,J,bi,bj)
293     StoreCTRLS1(I,J,bi,bj,8) = xx_aqh1(I,J,bi,bj)
294     # else
295     StoreCTRLS1(I,J,bi,bj,7) = 0.0
296     StoreCTRLS1(I,J,bi,bj,8) = 0.0
297     # endif
298     # ifdef ALLOW_PRECIP_CONTROL
299     StoreCTRLS1(I,J,bi,bj,9) = xx_precip0(I,J,bi,bj)
300     StoreCTRLS1(I,J,bi,bj,10) = xx_precip1(I,J,bi,bj)
301     # else
302     StoreCTRLS1(I,J,bi,bj,9) = 0.0
303     StoreCTRLS1(I,J,bi,bj,10) = 0.0
304     # endif
305     # ifdef ALLOW_SWFLUX_CONTROL
306     StoreCTRLS1(I,J,bi,bj,11) = xx_swflux0(I,J,bi,bj)
307     StoreCTRLS1(I,J,bi,bj,12) = xx_swflux1(I,J,bi,bj)
308     # else
309     StoreCTRLS1(I,J,bi,bj,11) = 0.0
310     StoreCTRLS1(I,J,bi,bj,12) = 0.0
311     # endif
312     # ifdef ALLOW_SWDOWN_CONTROL
313     StoreCTRLS1(I,J,bi,bj,13) = xx_swdown0(I,J,bi,bj)
314     StoreCTRLS1(I,J,bi,bj,14) = xx_swdown1(I,J,bi,bj)
315     # else
316     StoreCTRLS1(I,J,bi,bj,13) = 0.0
317     StoreCTRLS1(I,J,bi,bj,14) = 0.0
318     # endif
319     # ifdef ALLOW_LWDOWN_CONTROL
320     StoreCTRLS1(I,J,bi,bj,15) = xx_lwdown0(I,J,bi,bj)
321     StoreCTRLS1(I,J,bi,bj,16) = xx_lwdown1(I,J,bi,bj)
322     # else
323     StoreCTRLS1(I,J,bi,bj,15) = 0.0
324     StoreCTRLS1(I,J,bi,bj,16) = 0.0
325     # endif
326     # ifdef ALLOW_APRESSURE_CONTROL
327     StoreCTRLS1(I,J,bi,bj,17) = xx_apressure0(I,J,bi,bj)
328     StoreCTRLS1(I,J,bi,bj,18) = xx_apressure1(I,J,bi,bj)
329     # else
330     StoreCTRLS1(I,J,bi,bj,17) = 0.0
331     StoreCTRLS1(I,J,bi,bj,18) = 0.0
332     # endif
333     enddo
334     enddo
335     enddo
336     enddo
337     #endif /* ALLOW_EXF */
338    
339     #ifdef ALLOW_OBCS
340     # ifdef ALLOW_OBCS_NORTH
341     C-- Over all tiles
342     DO bj = myByLo(myThid), myByHi(myThid)
343     DO bi = myBxLo(myThid), myBxHi(myThid)
344     C- 2D arrays
345     DO K=1,Nr
346     DO I=1-Olx,sNx+Olx
347     StoreOBCSN(I,Nr,bi,bj,1) = OBNt(I,Nr,bi,bj)
348     StoreOBCSN(I,Nr,bi,bj,2) = OBNs(I,Nr,bi,bj)
349     StoreOBCSN(I,Nr,bi,bj,3) = OBNu0(I,Nr,bi,bj)
350     StoreOBCSN(I,Nr,bi,bj,4) = OBNv0(I,Nr,bi,bj)
351     StoreOBCSN(I,Nr,bi,bj,5) = OBNt0(I,Nr,bi,bj)
352     StoreOBCSN(I,Nr,bi,bj,6) = OBNs0(I,Nr,bi,bj)
353     StoreOBCSN(I,Nr,bi,bj,7) = OBNu1(I,Nr,bi,bj)
354     StoreOBCSN(I,Nr,bi,bj,8) = OBNv1(I,Nr,bi,bj)
355     StoreOBCSN(I,Nr,bi,bj,9) = OBNt1(I,Nr,bi,bj)
356     StoreOBCSN(I,Nr,bi,bj,10) = OBNs1(I,Nr,bi,bj)
357     # ifdef ALLOW_OBCSN_CONTROL
358     StoreOBCSN(I,Nr,bi,bj,11) = xx_obcsn0(I,Nr,bi,bj,1)
359     StoreOBCSN(I,Nr,bi,bj,12) = xx_obcsn0(I,Nr,bi,bj,2)
360     StoreOBCSN(I,Nr,bi,bj,13) = xx_obcsn0(I,Nr,bi,bj,3)
361     StoreOBCSN(I,Nr,bi,bj,14) = xx_obcsn0(I,Nr,bi,bj,4)
362     StoreOBCSN(I,Nr,bi,bj,15) = xx_obcsn1(I,Nr,bi,bj,1)
363     StoreOBCSN(I,Nr,bi,bj,16) = xx_obcsn1(I,Nr,bi,bj,2)
364     StoreOBCSN(I,Nr,bi,bj,17) = xx_obcsn1(I,Nr,bi,bj,3)
365     StoreOBCSN(I,Nr,bi,bj,18) = xx_obcsn1(I,Nr,bi,bj,4)
366     # else
367     StoreOBCSN(I,Nr,bi,bj,11) = 0.0
368     StoreOBCSN(I,Nr,bi,bj,12) = 0.0
369     StoreOBCSN(I,Nr,bi,bj,13) = 0.0
370     StoreOBCSN(I,Nr,bi,bj,14) = 0.0
371     StoreOBCSN(I,Nr,bi,bj,15) = 0.0
372     StoreOBCSN(I,Nr,bi,bj,16) = 0.0
373     StoreOBCSN(I,Nr,bi,bj,17) = 0.0
374     StoreOBCSN(I,Nr,bi,bj,18) = 0.0
375     # endif
376     enddo
377     enddo
378     enddo
379     enddo
380     # endif /* ALLOW_OBCS_NORTH */
381    
382     # ifdef ALLOW_OBCS_SOUTH
383     C-- Over all tiles
384     DO bj = myByLo(myThid), myByHi(myThid)
385     DO bi = myBxLo(myThid), myBxHi(myThid)
386     C- 2D arrays
387     DO K=1,Nr
388     DO I=1-Olx,sNx+Olx
389     StoreOBCSS(I,Nr,bi,bj,1) = OBSt(I,Nr,bi,bj)
390     StoreOBCSS(I,Nr,bi,bj,2) = OBSs(I,Nr,bi,bj)
391     StoreOBCSS(I,Nr,bi,bj,3) = OBSu0(I,Nr,bi,bj)
392     StoreOBCSS(I,Nr,bi,bj,4) = OBSv0(I,Nr,bi,bj)
393     StoreOBCSS(I,Nr,bi,bj,5) = OBSt0(I,Nr,bi,bj)
394     StoreOBCSS(I,Nr,bi,bj,6) = OBSs0(I,Nr,bi,bj)
395     StoreOBCSS(I,Nr,bi,bj,7) = OBSu1(I,Nr,bi,bj)
396     StoreOBCSS(I,Nr,bi,bj,8) = OBSv1(I,Nr,bi,bj)
397     StoreOBCSS(I,Nr,bi,bj,9) = OBSt1(I,Nr,bi,bj)
398     StoreOBCSS(I,Nr,bi,bj,10)= OBSs1(I,Nr,bi,bj)
399     # ifdef ALLOW_OBCSS_CONTROL
400     StoreOBCSS(I,Nr,bi,bj,11) = xx_obcss0(I,Nr,bi,bj,1)
401     StoreOBCSS(I,Nr,bi,bj,12) = xx_obcss0(I,Nr,bi,bj,2)
402     StoreOBCSS(I,Nr,bi,bj,13) = xx_obcss0(I,Nr,bi,bj,3)
403     StoreOBCSS(I,Nr,bi,bj,14) = xx_obcss0(I,Nr,bi,bj,4)
404     StoreOBCSS(I,Nr,bi,bj,15) = xx_obcss1(I,Nr,bi,bj,1)
405     StoreOBCSS(I,Nr,bi,bj,16) = xx_obcss1(I,Nr,bi,bj,2)
406     StoreOBCSS(I,Nr,bi,bj,17) = xx_obcss1(I,Nr,bi,bj,3)
407     StoreOBCSS(I,Nr,bi,bj,18) = xx_obcss1(I,Nr,bi,bj,4)
408     # else
409     StoreOBCSS(I,Nr,bi,bj,11) = 0.0
410     StoreOBCSS(I,Nr,bi,bj,12) = 0.0
411     StoreOBCSS(I,Nr,bi,bj,13) = 0.0
412     StoreOBCSS(I,Nr,bi,bj,14) = 0.0
413     StoreOBCSS(I,Nr,bi,bj,15) = 0.0
414     StoreOBCSS(I,Nr,bi,bj,16) = 0.0
415     StoreOBCSS(I,Nr,bi,bj,17) = 0.0
416     StoreOBCSS(I,Nr,bi,bj,18) = 0.0
417     # endif
418     enddo
419     enddo
420     enddo
421     enddo
422     # endif /* ALLOW_OBCS_SOUTH */
423    
424     # ifdef ALLOW_OBCS_EAST
425     C-- Over all tiles
426     DO bj = myByLo(myThid), myByHi(myThid)
427     DO bi = myBxLo(myThid), myBxHi(myThid)
428     C- 2D arrays
429     DO K=1,Nr
430     DO J=1-Oly,sNy+Oly
431     StoreOBCSE(J,Nr,bi,bj,1) = OBEt(J,Nr,bi,bj)
432     StoreOBCSE(J,Nr,bi,bj,2) = OBEs(J,Nr,bi,bj)
433     StoreOBCSE(J,Nr,bi,bj,3) = OBEu0(J,Nr,bi,bj)
434     StoreOBCSE(J,Nr,bi,bj,4) = OBEv0(J,Nr,bi,bj)
435     StoreOBCSE(J,Nr,bi,bj,5) = OBEt0(J,Nr,bi,bj)
436     StoreOBCSE(J,Nr,bi,bj,6) = OBEs0(J,Nr,bi,bj)
437     StoreOBCSE(J,Nr,bi,bj,7) = OBEu1(J,Nr,bi,bj)
438     StoreOBCSE(J,Nr,bi,bj,8) = OBEv1(J,Nr,bi,bj)
439     StoreOBCSE(J,Nr,bi,bj,9) = OBEt1(J,Nr,bi,bj)
440     StoreOBCSE(J,Nr,bi,bj,10)= OBEs1(J,Nr,bi,bj)
441     # ifdef ALLOW_OBCSE_CONTROL
442     StoreOBCSE(J,Nr,bi,bj,11) = xx_obcse0(J,Nr,bi,bj,1)
443     StoreOBCSE(J,Nr,bi,bj,12) = xx_obcse0(J,Nr,bi,bj,2)
444     StoreOBCSE(J,Nr,bi,bj,13) = xx_obcse0(J,Nr,bi,bj,3)
445     StoreOBCSE(J,Nr,bi,bj,14) = xx_obcse0(J,Nr,bi,bj,4)
446     StoreOBCSE(J,Nr,bi,bj,15) = xx_obcse1(J,Nr,bi,bj,1)
447     StoreOBCSE(J,Nr,bi,bj,16) = xx_obcse1(J,Nr,bi,bj,2)
448     StoreOBCSE(J,Nr,bi,bj,17) = xx_obcse1(J,Nr,bi,bj,3)
449     StoreOBCSE(J,Nr,bi,bj,18) = xx_obcse1(J,Nr,bi,bj,4)
450     # else
451     StoreOBCSE(J,Nr,bi,bj,11) = 0.0
452     StoreOBCSE(J,Nr,bi,bj,12) = 0.0
453     StoreOBCSE(J,Nr,bi,bj,13) = 0.0
454     StoreOBCSE(J,Nr,bi,bj,14) = 0.0
455     StoreOBCSE(J,Nr,bi,bj,15) = 0.0
456     StoreOBCSE(J,Nr,bi,bj,16) = 0.0
457     StoreOBCSE(J,Nr,bi,bj,17) = 0.0
458     StoreOBCSE(J,Nr,bi,bj,18) = 0.0
459     # endif
460     enddo
461     enddo
462     enddo
463     enddo
464     # endif /* ALLOW_OBCS_EAST */
465    
466     # ifdef ALLOW_OBCS_WEST
467     C-- Over all tiles
468     DO bj = myByLo(myThid), myByHi(myThid)
469     DO bi = myBxLo(myThid), myBxHi(myThid)
470     C- 2D arrays
471     DO K=1,Nr
472     DO J=1-Oly,sNy+Oly
473     StoreOBCSW(J,Nr,bi,bj,1) = OBWt(J,Nr,bi,bj)
474     StoreOBCSW(J,Nr,bi,bj,2) = OBWs(J,Nr,bi,bj)
475     StoreOBCSW(J,Nr,bi,bj,3) = OBWu0(J,Nr,bi,bj)
476     StoreOBCSW(J,Nr,bi,bj,4) = OBWv0(J,Nr,bi,bj)
477     StoreOBCSW(J,Nr,bi,bj,5) = OBWt0(J,Nr,bi,bj)
478     StoreOBCSW(J,Nr,bi,bj,6) = OBWs0(J,Nr,bi,bj)
479     StoreOBCSW(J,Nr,bi,bj,7) = OBWu1(J,Nr,bi,bj)
480     StoreOBCSW(J,Nr,bi,bj,8) = OBWv1(J,Nr,bi,bj)
481     StoreOBCSW(J,Nr,bi,bj,9) = OBWt1(J,Nr,bi,bj)
482     StoreOBCSW(J,Nr,bi,bj,10)= OBWs1(J,Nr,bi,bj)
483     # ifdef ALLOW_OBCSW_CONTROL
484     StoreOBCSW(J,Nr,bi,bj,11) = xx_obcsw0(J,Nr,bi,bj,1)
485     StoreOBCSW(J,Nr,bi,bj,12) = xx_obcsw0(J,Nr,bi,bj,2)
486     StoreOBCSW(J,Nr,bi,bj,13) = xx_obcsw0(J,Nr,bi,bj,3)
487     StoreOBCSW(J,Nr,bi,bj,14) = xx_obcsw0(J,Nr,bi,bj,4)
488     StoreOBCSW(J,Nr,bi,bj,15) = xx_obcsw1(J,Nr,bi,bj,1)
489     StoreOBCSW(J,Nr,bi,bj,16) = xx_obcsw1(J,Nr,bi,bj,2)
490     StoreOBCSW(J,Nr,bi,bj,17) = xx_obcsw1(J,Nr,bi,bj,3)
491     StoreOBCSW(J,Nr,bi,bj,18) = xx_obcsw1(J,Nr,bi,bj,4)
492     # else
493     StoreOBCSW(J,Nr,bi,bj,11) = 0.0
494     StoreOBCSW(J,Nr,bi,bj,12) = 0.0
495     StoreOBCSW(J,Nr,bi,bj,13) = 0.0
496     StoreOBCSW(J,Nr,bi,bj,14) = 0.0
497     StoreOBCSW(J,Nr,bi,bj,15) = 0.0
498     StoreOBCSW(J,Nr,bi,bj,16) = 0.0
499     StoreOBCSW(J,Nr,bi,bj,17) = 0.0
500     StoreOBCSW(J,Nr,bi,bj,18) = 0.0
501     # endif
502     enddo
503     enddo
504     enddo
505     enddo
506     # endif /* ALLOW_OBCS_WEST */
507     #endif /* ALLOW_OBCS */
508    
509     #ifdef ALLOW_SEAICE
510     C-- Over all tiles
511     DO bj = myByLo(myThid), myByHi(myThid)
512     DO bi = myBxLo(myThid), myBxHi(myThid)
513     C- 2D arrays
514     DO J=1-Oly,sNy+Oly
515     DO I=1-Olx,sNx+Olx
516     StoreSEAICE(I,J,bi,bj,1) = AREA(I,J,1,bi,bj)
517     StoreSEAICE(I,J,bi,bj,2) = AREA(I,J,2,bi,bj)
518     StoreSEAICE(I,J,bi,bj,3) = AREA(I,J,3,bi,bj)
519     StoreSEAICE(I,J,bi,bj,4) = HEFF(I,J,1,bi,bj)
520     StoreSEAICE(I,J,bi,bj,5) = HEFF(I,J,2,bi,bj)
521     StoreSEAICE(I,J,bi,bj,6) = HEFF(I,J,3,bi,bj)
522     StoreSEAICE(I,J,bi,bj,7) = HSNOW(I,J,bi,bj)
523     StoreSEAICE(I,J,bi,bj,8) = TICE(I,J,bi,bj)
524     StoreSEAICE(I,J,bi,bj,9) = RUNOFF(I,J,bi,bj)
525     # ifdef SEAICE_MULTICATEGORY
526     StoreSEAICE(I,J,bi,bj,10) = TICES(I,J,bi,bj)
527     # else
528     StoreSEAICE(I,J,bi,bj,10) = 0.0
529     # endif
530     # ifdef SEAICE_ALLOW_DYNAMICS
531     StoreSEAICE(I,J,bi,bj,11) = UICE(I,J,1,bi,bj)
532     StoreSEAICE(I,J,bi,bj,12) = UICE(I,J,2,bi,bj)
533     StoreSEAICE(I,J,bi,bj,13) = UICE(I,J,3,bi,bj)
534     StoreSEAICE(I,J,bi,bj,14) = VICE(I,J,1,bi,bj)
535     StoreSEAICE(I,J,bi,bj,15) = VICE(I,J,2,bi,bj)
536     StoreSEAICE(I,J,bi,bj,16) = VICE(I,J,3,bi,bj)
537     StoreSEAICE(I,J,bi,bj,17) = ZETA(I,J,bi,bj)
538     StoreSEAICE(I,J,bi,bj,18) = ETA(I,J,bi,bj)
539     # ifdef SEAICE_CGRID
540     StoreSEAICE(I,J,bi,bj,19) = dwatn(I,J,bi,bj)
541     StoreSEAICE(I,J,bi,bj,20) = seaicemasku(I,J,bi,bj)
542     StoreSEAICE(I,J,bi,bj,21) = seaicemaskv(I,J,bi,bj)
543     # else
544     StoreSEAICE(I,J,bi,bj,19) = 0.0
545     StoreSEAICE(I,J,bi,bj,20) = 0.0
546     StoreSEAICE(I,J,bi,bj,21) = 0.0
547     # endif /* SEAICE_CGRID */
548     # ifdef SEAICE_ALLOW_EVP
549     StoreSEAICE(I,J,bi,bj,22) = seaice_sigma1(I,J,bi,bj)
550     StoreSEAICE(I,J,bi,bj,23) = seaice_sigma2(I,J,bi,bj)
551     StoreSEAICE(I,J,bi,bj,24) = seaice_sigma12(I,J,bi,bj)
552     # else
553     StoreSEAICE(I,J,bi,bj,22) = 0.0
554     StoreSEAICE(I,J,bi,bj,23) = 0.0
555     StoreSEAICE(I,J,bi,bj,24) = 0.0
556     # endif /* SEAICE_ALLOW_EVP */
557     # else
558     StoreSEAICE(I,J,bi,bj,11) = 0.0
559     StoreSEAICE(I,J,bi,bj,12) = 0.0
560     StoreSEAICE(I,J,bi,bj,13) = 0.0
561     StoreSEAICE(I,J,bi,bj,14) = 0.0
562     StoreSEAICE(I,J,bi,bj,15) = 0.0
563     StoreSEAICE(I,J,bi,bj,16) = 0.0
564     StoreSEAICE(I,J,bi,bj,17) = 0.0
565     StoreSEAICE(I,J,bi,bj,18) = 0.0
566     StoreSEAICE(I,J,bi,bj,19) = 0.0
567     StoreSEAICE(I,J,bi,bj,20) = 0.0
568     StoreSEAICE(I,J,bi,bj,21) = 0.0
569     StoreSEAICE(I,J,bi,bj,22) = 0.0
570     StoreSEAICE(I,J,bi,bj,23) = 0.0
571     StoreSEAICE(I,J,bi,bj,24) = 0.0
572     # endif /* SEAICE_ALLOW_DYNAMICS */
573 heimbach 1.3 # ifdef SEAICE_SALINITY
574     StoreSEAICE(I,J,bi,bj,25) = HSALT(I,J,bi,bj)
575     # else
576     StoreSEAICE(I,J,bi,bj,25) = 0.0
577     # endif
578 heimbach 1.1 enddo
579     enddo
580     enddo
581     enddo
582     #endif /* ALLOW_SEAICE */
583    
584     #ifndef DISABLE_DEBUGMODE
585     IF ( debugLevel .GE. debLevB )
586     & CALL DEBUG_LEAVE('AUTODIFF_STORE',myThid)
587     #endif
588    
589     #endif /* ALLOW_AUTODIFF_TAMC */
590     c**************************************
591    
592     return
593     end
594    

  ViewVC Help
Powered by ViewVC 1.1.22