/[MITgcm]/MITgcm/pkg/seaice/seaice_advdiff.F
ViewVC logotype

Contents of /MITgcm/pkg/seaice/seaice_advdiff.F

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


Revision 1.43 - (show annotations) (download)
Fri Dec 17 04:02:25 2010 UTC (13 years, 5 months ago) by gforget
Branch: MAIN
CVS Tags: checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62t
Changes since 1.42: +1 -5 lines
-avoid recomputation.
-add seaice_diffusion.f seaice_map_thsice.f to adjoint.
-allow use of multidim advection in ad runs.

1 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_advdiff.F,v 1.42 2010/06/30 02:13:54 jmc Exp $
2 C $Name: $
3
4 #include "SEAICE_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: SEAICE_ADVDIFF
8
9 C !INTERFACE: ==========================================================
10 SUBROUTINE SEAICE_ADVDIFF(
11 I myTime, myIter, myThid )
12
13 C !DESCRIPTION: \bv
14 C *===========================================================*
15 C | SUBROUTINE SEAICE_ADVDIFF
16 C | o driver for different advection routines
17 C | calls an adaption of gad_advection to call different
18 C | advection routines of pkg/generic_advdiff
19 C *===========================================================*
20 C \ev
21
22 C !USES: ===============================================================
23 IMPLICIT NONE
24
25 C === Global variables ===
26 C UICE/VICE :: ice velocity
27 C HEFF :: scalar field to be advected
28 C HEFFM :: mask for scalar field
29 #include "SIZE.h"
30 #include "EEPARAMS.h"
31 #include "PARAMS.h"
32 #include "GRID.h"
33 #include "GAD.h"
34 #include "SEAICE_PARAMS.h"
35 #include "SEAICE.h"
36
37 #ifdef ALLOW_AUTODIFF_TAMC
38 # include "tamc.h"
39 #endif
40
41 C !INPUT PARAMETERS: ===================================================
42 C === Routine arguments ===
43 C myTime :: current time
44 C myIter :: iteration number
45 C myThid :: Thread no. that called this routine.
46 _RL myTime
47 INTEGER myIter
48 INTEGER myThid
49 CEndOfInterface
50
51 C !LOCAL VARIABLES: ====================================================
52 C === Local variables ===
53 C i,j,bi,bj :: Loop counters
54 C ks :: surface level index
55 C uc/vc :: current ice velocity on C-grid
56 C uTrans :: volume transport, x direction
57 C vTrans :: volume transport, y direction
58 C iceFld :: copy of seaice field
59 C afx :: horizontal advective flux, x direction
60 C afy :: horizontal advective flux, y direction
61 C gFld :: tendency of seaice field
62 C xA,yA :: "areas" of X and Y face of tracer cells
63 INTEGER i, j, bi, bj
64 INTEGER ks
65 LOGICAL SEAICEmultiDimAdvection
66
67 C- MPI+MTH: apply exch (sure with exch1) only to array in common block
68 COMMON / SEAICE_ADVDIFF_LOCAL / uc, vc
69 _RL uc (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
70 _RL vc (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
71 _RL fldNm1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
72 _RL uTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
73 _RL vTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
74 c _RL iceFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
75 _RL afx (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
76 _RL afy (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
77 _RL gFld (1-Olx:sNx+Olx,1-Oly:sNy+Oly)
78 _RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
79 _RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
80 _RL recip_heff(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
81 CEOP
82
83 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
84
85 ks = 1
86
87 C-- make a local copy of the velocities for compatibility with B-grid
88 C-- alternatively interpolate to C-points if necessary
89 DO bj=myByLo(myThid),myByHi(myThid)
90 DO bi=myBxLo(myThid),myBxHi(myThid)
91 #ifdef SEAICE_CGRID
92 DO j=1-Oly,sNy+Oly
93 DO i=1-Olx,sNx+Olx
94 uc(i,j,bi,bj)=UICE(i,j,bi,bj)
95 vc(i,j,bi,bj)=VICE(i,j,bi,bj)
96 ENDDO
97 ENDDO
98 #else /* not SEAICE_CGRID = BGRID */
99 C average seaice velocity to C-grid
100 DO j=1-Oly,sNy+Oly-1
101 DO i=1-Olx,sNx+Olx-1
102 uc(i,j,bi,bj)=.5 _d 0*(UICE(i,j,bi,bj)+UICE(i,j+1,bi,bj))
103 vc(i,j,bi,bj)=.5 _d 0*(VICE(i,j,bi,bj)+VICE(I+1,J,bi,bj))
104 ENDDO
105 ENDDO
106 #endif /* SEAICE_CGRID */
107 ENDDO
108 ENDDO
109
110 #ifndef SEAICE_CGRID
111 C Do we need this? I am afraid so.
112 CALL EXCH_UV_XY_RL(uc,vc,.TRUE.,myThid)
113 #endif /* not SEAICE_CGRID */
114
115 SEAICEmultidimadvection = .TRUE.
116 IF ( SEAICEadvScheme.EQ.ENUM_CENTERED_2ND
117 & .OR.SEAICEadvScheme.EQ.ENUM_UPWIND_3RD
118 & .OR.SEAICEadvScheme.EQ.ENUM_CENTERED_4TH ) THEN
119 SEAICEmultiDimAdvection = .FALSE.
120 ENDIF
121
122
123 #ifdef ALLOW_AUTODIFF_TAMC
124 CADJ STORE area = comlev1, key = ikey_dynamics, kind=isbyte
125 CADJ STORE heff = comlev1, key = ikey_dynamics, kind=isbyte
126 CADJ STORE heffm = comlev1, key = ikey_dynamics, kind=isbyte
127 CADJ STORE hsnow = comlev1, key = ikey_dynamics, kind=isbyte
128 # ifdef SEAICE_SALINITY
129 CADJ STORE hsalt = comlev1, key = ikey_dynamics, kind=isbyte
130 # endif
131 #endif /* ALLOW_AUTODIFF_TAMC */
132 IF ( SEAICEmultiDimAdvection ) THEN
133 C This has to be done to comply with the time stepping in advect.F:
134 C Making sure that the following routines see the different
135 C time levels correctly
136 C At the end of the routine ADVECT,
137 C timelevel 1 is updated with advection contribution
138 C and diffusion contribution
139 C (which was computed in DIFFUS on timelevel 3)
140 C timelevel 2 is the previous timelevel 1
141 C timelevel 3 is the total diffusion tendency * deltaT
142 C (empty if no diffusion)
143
144 #ifdef ALLOW_AUTODIFF_TAMC
145 CADJ STORE uc = comlev1, key = ikey_dynamics, kind=isbyte
146 CADJ STORE vc = comlev1, key = ikey_dynamics, kind=isbyte
147 #endif /* ALLOW_AUTODIFF_TAMC */
148
149 DO bj=myByLo(myThid),myByHi(myThid)
150 DO bi=myBxLo(myThid),myBxHi(myThid)
151 C--- loops on tile indices bi,bj
152
153 #ifdef ALLOW_AUTODIFF_TAMC
154 C Initialise for TAF
155 DO j=1-Oly,sNy+Oly
156 DO i=1-Olx,sNx+Olx
157 c iceFld(i,j) = 0. _d 0
158 gFld(i,j) = 0. _d 0
159 ENDDO
160 ENDDO
161 #endif /* ALLOW_AUTODIFF_TAMC */
162
163 DO j=1-OLy,sNy+OLy
164 DO i=1-OLx,sNx+OLx
165 HEFFNM1(i,j,bi,bj) = HEFF(i,j,bi,bj)
166 AREANM1(i,j,bi,bj) = AREA(i,j,bi,bj)
167 recip_heff(i,j) = 1. _d 0
168 ENDDO
169 ENDDO
170
171 C- first compute cell areas used by all tracers
172 DO j=1-Oly,sNy+Oly
173 DO i=1-Olx,sNx+Olx
174 xA(i,j) = _dyG(i,j,bi,bj)*_maskW(i,j,ks,bi,bj)
175 yA(i,j) = _dxG(i,j,bi,bj)*_maskS(i,j,ks,bi,bj)
176 ENDDO
177 ENDDO
178 C- Calculate "volume transports" through tracer cell faces.
179 DO j=1-Oly,sNy+Oly
180 DO i=1-Olx,sNx+Olx
181 uTrans(i,j) = uc(i,j,bi,bj)*xA(i,j)
182 vTrans(i,j) = vc(i,j,bi,bj)*yA(i,j)
183 ENDDO
184 ENDDO
185
186 C-- Effective Thickness (Volume)
187 IF ( SEAICEadvHeff ) THEN
188 CALL SEAICE_ADVECTION(
189 I GAD_HEFF, SEAICEadvSchHeff,
190 I uc(1-OLx,1-OLy,bi,bj), vc(1-OLx,1-OLy,bi,bj),
191 I uTrans, vTrans, HEFF(1-OLx,1-OLy,bi,bj), recip_heff,
192 O gFld, afx, afy,
193 I bi, bj, myTime, myIter, myThid )
194 IF ( diff1 .GT. 0. _d 0 ) THEN
195 C- Add tendency due to diffusion
196 CALL SEAICE_DIFFUSION(
197 I GAD_HEFF,
198 I HEFF(1-OLx,1-OLy,bi,bj), HEFFM, xA, yA,
199 U gFld,
200 I bi, bj, myTime, myIter, myThid )
201 ENDIF
202 C now do the "explicit" time step
203 DO j=1,sNy
204 DO i=1,sNx
205 HEFF(i,j,bi,bj) = HEFFM(i,j,bi,bj) * (
206 & HEFF(i,j,bi,bj) + SEAICE_deltaTtherm * gFld(i,j)
207 & )
208 ENDDO
209 ENDDO
210 ENDIF
211
212 C-- Fractional area
213 IF ( SEAICEadvArea ) THEN
214 CALL SEAICE_ADVECTION(
215 I GAD_AREA, SEAICEadvSchArea,
216 I uc(1-OLx,1-OLy,bi,bj), vc(1-OLx,1-OLy,bi,bj),
217 I uTrans, vTrans, AREA(1-OLx,1-OLy,bi,bj), recip_heff,
218 O gFld, afx, afy,
219 I bi, bj, myTime, myIter, myThid )
220 IF ( diff1 .GT. 0. _d 0 ) THEN
221 C- Add tendency due to diffusion
222 CALL SEAICE_DIFFUSION(
223 I GAD_AREA,
224 I AREA(1-OLx,1-OLy,bi,bj), HEFFM, xA, yA,
225 U gFld,
226 I bi, bj, myTime, myIter, myThid )
227 ENDIF
228 C now do the "explicit" time step
229 DO j=1,sNy
230 DO i=1,sNx
231 AREA(i,j,bi,bj) = HEFFM(i,j,bi,bj) * (
232 & AREA(i,j,bi,bj) + SEAICE_deltaTtherm * gFld(i,j)
233 & )
234 ENDDO
235 ENDDO
236 ENDIF
237
238 C-- Effective Snow Thickness (Volume)
239 IF ( SEAICEadvSnow ) THEN
240 CALL SEAICE_ADVECTION(
241 I GAD_SNOW, SEAICEadvSchSnow,
242 I uc(1-OLx,1-OLy,bi,bj), vc(1-OLx,1-OLy,bi,bj),
243 I uTrans, vTrans, HSNOW(1-OLx,1-OLy,bi,bj), recip_heff,
244 O gFld, afx, afy,
245 I bi, bj, myTime, myIter, myThid )
246 IF ( diff1 .GT. 0. _d 0 ) THEN
247 C-- Add tendency due to diffusion
248 CALL SEAICE_DIFFUSION(
249 I GAD_SNOW,
250 I HSNOW(1-OLx,1-OLy,bi,bj), HEFFM, xA, yA,
251 U gFld,
252 I bi, bj, myTime, myIter, myThid )
253 ENDIF
254 C now do the "explicit" time step
255 DO j=1,sNy
256 DO i=1,sNx
257 HSNOW(i,j,bi,bj) = HEFFM(i,j,bi,bj) * (
258 & HSNOW(i,j,bi,bj) + SEAICE_deltaTtherm * gFld(i,j)
259 & )
260 ENDDO
261 ENDDO
262 ENDIF
263
264 #ifdef SEAICE_SALINITY
265 C-- Effective Sea Ice Salinity (Mass of salt)
266 IF ( SEAICEadvSalt ) THEN
267 CALL SEAICE_ADVECTION(
268 I GAD_SALT, SEAICEadvSchSalt,
269 I uc(1-OLx,1-OLy,bi,bj), vc(1-OLx,1-OLy,bi,bj),
270 I uTrans, vTrans, HSALT(1-OLx,1-OLy,bi,bj), recip_heff,
271 O gFld, afx, afy,
272 I bi, bj, myTime, myIter, myThid )
273 IF ( diff1 .GT. 0. _d 0 ) THEN
274 C-- Add tendency due to diffusion
275 CALL SEAICE_DIFFUSION(
276 I GAD_SALT,
277 I HSALT(1-OLx,1-OLy,bi,bj), HEFFM, xA, yA,
278 U gFld,
279 I bi, bj, myTime, myIter, myThid )
280 ENDIF
281 C now do the "explicit" time step
282 DO j=1,sNy
283 DO i=1,sNx
284 HSALT(i,j,bi,bj) = HEFFM(i,j,bi,bj) * (
285 & HSALT(i,j,bi,bj) + SEAICE_deltaTtherm * gFld(i,j)
286 & )
287 ENDDO
288 ENDDO
289 ENDIF
290 #endif /* SEAICE_SALINITY */
291
292 #ifdef SEAICE_AGE
293 C-- Sea Ice Age
294 IF ( SEAICEadvAge ) THEN
295 CALL SEAICE_ADVECTION(
296 I GAD_AGE, SEAICEadvSchAge,
297 I uc(1-OLx,1-OLy,bi,bj), vc(1-OLx,1-OLy,bi,bj),
298 I uTrans, vTrans, IceAge(1-OLx,1-OLy,bi,bj), recip_heff,
299 O gFld, afx, afy,
300 I bi, bj, myTime, myIter, myThid )
301 IF ( diff1 .GT. 0. _d 0 ) THEN
302 C-- Add tendency due to diffusion
303 CALL SEAICE_DIFFUSION(
304 I GAD_AGE,
305 I IceAge(1-OLx,1-OLy,bi,bj), HEFFM, xA, yA,
306 U gFld,
307 I bi, bj, myTime, myIter, myThid )
308 ENDIF
309 C now do the "explicit" time step
310 DO j=1,sNy
311 DO i=1,sNx
312 IceAge(i,j,bi,bj) = HEFFM(i,j,bi,bj) * (
313 & IceAge(i,j,bi,bj) + SEAICE_deltaTtherm * gFld(i,j)
314 & )
315 ENDDO
316 ENDDO
317 ENDIF
318 #endif /* SEAICE_AGE */
319
320 C--- end bi,bj loops
321 ENDDO
322 ENDDO
323
324 ELSE
325 C-- if not multiDimAdvection
326
327 #ifdef ALLOW_AUTODIFF_TAMC
328 CADJ STORE uc = comlev1, key = ikey_dynamics, kind=isbyte
329 CADJ STORE vc = comlev1, key = ikey_dynamics, kind=isbyte
330 #endif /* ALLOW_AUTODIFF_TAMC */
331
332 IF ( SEAICEadvHEff ) THEN
333 CALL ADVECT( uc, vc, hEff, hEffNm1, HEFFM, myThid )
334 ENDIF
335 IF ( SEAICEadvArea ) THEN
336 CALL ADVECT( uc, vc, area, areaNm1, HEFFM, myThid )
337 ENDIF
338 IF ( SEAICEadvSnow ) THEN
339 CALL ADVECT( uc, vc, HSNOW, fldNm1, HEFFM, myThid )
340 ENDIF
341
342 #ifdef SEAICE_SALINITY
343 IF ( SEAICEadvSalt ) THEN
344 CALL ADVECT( uc, vc, HSALT, fldNm1, HEFFM, myThid )
345 ENDIF
346 #endif /* SEAICE_SALINITY */
347
348 #ifdef SEAICE_AGE
349 IF ( SEAICEadvAge ) THEN
350 CALL ADVECT( uc, vc, iceAge, fldNm1, HEFFM, myThid )
351 ENDIF
352 #endif /* SEAICE_AGE */
353
354 C-- end if multiDimAdvection
355 ENDIF
356
357 #ifdef ALLOW_AUTODIFF_TAMC
358 CADJ STORE AREA = comlev1, key = ikey_dynamics, kind=isbyte
359 #endif
360 IF ( .NOT. usePW79thermodynamics ) THEN
361 C Hiblers "ridging function": Do it now if not in seaice_growth
362 C in principle we should add a "real" ridging function here (or
363 C somewhere after doing the advection)
364 DO bj=myByLo(myThid),myByHi(myThid)
365 DO bi=myBxLo(myThid),myBxHi(myThid)
366 DO j=1-Oly,sNy+Oly
367 DO i=1-Olx,sNx+Olx
368 #ifdef SEAICE_AGE
369 C avoid ridging of sea ice age (at this point ridged ice means AREA > 1)
370 IceAge(I,J,bi,bj) = IceAge(I,J,bi,bj)
371 & / MAX(ONE,AREA(I,J,bi,bj))
372 #endif /* SEAICE_AGE */
373 AREA(I,J,bi,bj) = MIN(ONE,AREA(I,J,bi,bj))
374 ENDDO
375 ENDDO
376 ENDDO
377 ENDDO
378 #ifdef SEAICE_AGE
379 C Sources and sinks for sea ice age (otherwise added in seaice_growth)
380 IF ( .TRUE. ) THEN
381 DO bj=myByLo(myThid),myByHi(myThid)
382 DO bi=myBxLo(myThid),myBxHi(myThid)
383 DO J=1,sNy
384 DO I=1,sNx
385 IF ( AREA(I,J,bi,bj) .GT. 0.15 ) THEN
386 IceAge(i,j,bi,bj) = IceAge(i,j,bi,bj) +
387 & AREA(I,J,bi,bj) * SEAICE_deltaTtherm
388 ELSE
389 IceAge(i,j,bi,bj) = ZERO
390 ENDIF
391 ENDDO
392 ENDDO
393 ENDDO
394 ENDDO
395 ENDIF
396 #endif /* SEAICE_AGE */
397 ENDIF
398
399 RETURN
400 END

  ViewVC Help
Powered by ViewVC 1.1.22