/[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.12 - (hide annotations) (download)
Mon Aug 9 16:05:22 2010 UTC (13 years, 11 months ago) by gforget
Branch: MAIN
CVS Tags: checkpoint62j
Changes since 1.11: +18 -5 lines
Storage directives allowing the use of
Adam-Bashforth-3 time stepping in adjoint.

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

  ViewVC Help
Powered by ViewVC 1.1.22