/[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.17 - (hide annotations) (download)
Thu Apr 28 02:06:31 2011 UTC (13 years, 2 months ago) by ifenty
Branch: MAIN
CVS Tags: checkpoint62x
Changes since 1.16: +2 -2 lines
Renaming of compile time flag SEAICE_SALINITY to SEAICE_VARIABLE_SALINITY and
SEAICE_salinity to SIsalFRAC.

Added logical checks for the use of the retired variable names in
 seaice_readparms and seaice_check.

 ----------------------------------------------------------------------
 Modified Files:
 	pkg/autodiff/autodiff_restore.F pkg/autodiff/autodiff_store.F
 	pkg/obcs/obcs_apply_seaice.F pkg/seaice/SEAICE.h
 	pkg/seaice/SEAICE_OPTIONS.h pkg/seaice/SEAICE_PARAMS.h
 	pkg/seaice/seaice_ad_check_lev1_dir.h
 	pkg/seaice/seaice_advdiff.F pkg/seaice/seaice_check.F
 	pkg/seaice/seaice_diagnostics_state.F
 	pkg/seaice/seaice_growth.F pkg/seaice/seaice_init_varia.F
 	pkg/seaice/seaice_model.F pkg/seaice/seaice_monitor.F
 	pkg/seaice/seaice_output.F pkg/seaice/seaice_read_pickup.F
 	pkg/seaice/seaice_readparms.F pkg/seaice/seaice_write_pickup.F
 ----------------------------------------------------------------------

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

  ViewVC Help
Powered by ViewVC 1.1.22