/[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.51 - (show annotations) (download)
Thu Jun 9 19:37:01 2011 UTC (13 years ago) by gforget
Branch: MAIN
Changes since 1.50: +71 -18 lines
- seaice_tracer_phys.F and seaice_advdiff.F
  do ice cover tracers, in addition to ice volume tracers.
- seaice_readparms.F
  add SItrMate ('HEFF' or 'AREA') in PARAMS03 to switch
    from ice volume tracer (defualt) to ice cover tracer
- seaice_growth.F
  use areaMax in AREA update (part 4), consistent with ridging step (part 2.5).
  store AREA in SItrAREA at the ridging and update steps (for use with SItracer).

1 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_advdiff.F,v 1.50 2011/06/07 03:58:23 gforget 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_SIZE.h"
35 #include "SEAICE_PARAMS.h"
36 #include "SEAICE.h"
37 #include "SEAICE_TRACER.h"
38
39 #ifdef ALLOW_AUTODIFF_TAMC
40 # include "tamc.h"
41 #endif
42
43 C !INPUT PARAMETERS: ===================================================
44 C === Routine arguments ===
45 C myTime :: current time
46 C myIter :: iteration number
47 C myThid :: Thread no. that called this routine.
48 _RL myTime
49 INTEGER myIter
50 INTEGER myThid
51 CEndOfInterface
52
53 C !LOCAL VARIABLES: ====================================================
54 C === Local variables ===
55 C i,j,bi,bj :: Loop counters
56 C ks :: surface level index
57 C uc/vc :: current ice velocity on C-grid
58 C uTrans :: volume transport, x direction
59 C vTrans :: volume transport, y direction
60 C iceFld :: copy of seaice field
61 C afx :: horizontal advective flux, x direction
62 C afy :: horizontal advective flux, y direction
63 C gFld :: tendency of seaice field
64 C xA,yA :: "areas" of X and Y face of tracer cells
65 INTEGER i, j, bi, bj
66 INTEGER ks
67 LOGICAL SEAICEmultiDimAdvection
68 #ifdef ALLOW_SITRACER
69 INTEGER iTr, SEAICEadvSchSItr, SEAICEdiffKhSItr
70 _RL SItrExt (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
71 _RL tmpscal1, tmpscal2
72 #ifdef ALLOW_SITRACER_ADVCAP
73 _RL SItrPrev (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
74 #endif
75 #ifdef ALLOW_SITRACER_DIAG
76 _RL DIAGarray (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
77 #endif
78 #endif
79 #ifdef SEAICE_AGE
80 INTEGER iTracer
81 #endif
82
83 _RL uc (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
84 _RL vc (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
85 _RL fldNm1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
86 _RL uTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
87 _RL vTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
88 c _RL iceFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
89 _RL afx (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
90 _RL afy (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
91 _RL gFld (1-Olx:sNx+Olx,1-Oly:sNy+Oly)
92 _RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
93 _RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
94 _RL recip_heff(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
95 CEOP
96
97 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
98
99 ks = 1
100
101 C-- make a local copy of the velocities for compatibility with B-grid
102 C-- alternatively interpolate to C-points if necessary
103 DO bj=myByLo(myThid),myByHi(myThid)
104 DO bi=myBxLo(myThid),myBxHi(myThid)
105 #ifdef SEAICE_CGRID
106 DO j=1-Oly,sNy+Oly
107 DO i=1-Olx,sNx+Olx
108 uc(i,j,bi,bj)=UICE(i,j,bi,bj)
109 vc(i,j,bi,bj)=VICE(i,j,bi,bj)
110 ENDDO
111 ENDDO
112 #else /* not SEAICE_CGRID = BGRID */
113 C average seaice velocity to C-grid
114 DO j=1-Oly,sNy+Oly-1
115 DO i=1-Olx,sNx+Olx-1
116 uc(i,j,bi,bj)=.5 _d 0*(UICE(i,j,bi,bj)+UICE(i,j+1,bi,bj))
117 vc(i,j,bi,bj)=.5 _d 0*(VICE(i,j,bi,bj)+VICE(i+1,j,bi,bj))
118 ENDDO
119 ENDDO
120 #endif /* SEAICE_CGRID */
121 C- compute cell areas used by all tracers
122 DO j=1-Oly,sNy+Oly
123 DO i=1-Olx,sNx+Olx
124 xA(i,j,bi,bj) = _dyG(i,j,bi,bj)*_maskW(i,j,ks,bi,bj)
125 yA(i,j,bi,bj) = _dxG(i,j,bi,bj)*_maskS(i,j,ks,bi,bj)
126 ENDDO
127 ENDDO
128 ENDDO
129 ENDDO
130
131 #ifndef SEAICE_CGRID
132 C Do we need this? I am afraid so.
133 CALL EXCH_UV_XY_RL(uc,vc,.TRUE.,myThid)
134 #endif /* not SEAICE_CGRID */
135
136 SEAICEmultidimadvection = .TRUE.
137 IF ( SEAICEadvScheme.EQ.ENUM_CENTERED_2ND
138 & .OR.SEAICEadvScheme.EQ.ENUM_UPWIND_3RD
139 & .OR.SEAICEadvScheme.EQ.ENUM_CENTERED_4TH ) THEN
140 SEAICEmultiDimAdvection = .FALSE.
141 ENDIF
142
143
144 #ifdef ALLOW_AUTODIFF_TAMC
145 CADJ STORE area = comlev1, key = ikey_dynamics, kind=isbyte
146 CADJ STORE heff = comlev1, key = ikey_dynamics, kind=isbyte
147 CADJ STORE heffm = comlev1, key = ikey_dynamics, kind=isbyte
148 CADJ STORE hsnow = comlev1, key = ikey_dynamics, kind=isbyte
149 # ifdef SEAICE_VARIABLE_SALINITY
150 CADJ STORE hsalt = comlev1, key = ikey_dynamics, kind=isbyte
151 # endif
152 #endif /* ALLOW_AUTODIFF_TAMC */
153 IF ( SEAICEmultiDimAdvection ) THEN
154 C This has to be done to comply with the time stepping in advect.F:
155 C Making sure that the following routines see the different
156 C time levels correctly
157 C At the end of the routine ADVECT,
158 C timelevel 1 is updated with advection contribution
159 C and diffusion contribution
160 C (which was computed in DIFFUS on timelevel 3)
161 C timelevel 2 is the previous timelevel 1
162 C timelevel 3 is the total diffusion tendency * deltaT
163 C (empty if no diffusion)
164
165 #ifdef ALLOW_AUTODIFF_TAMC
166 CADJ STORE uc = comlev1, key = ikey_dynamics, kind=isbyte
167 CADJ STORE vc = comlev1, key = ikey_dynamics, kind=isbyte
168 #endif /* ALLOW_AUTODIFF_TAMC */
169
170 DO bj=myByLo(myThid),myByHi(myThid)
171 DO bi=myBxLo(myThid),myBxHi(myThid)
172 C--- loops on tile indices bi,bj
173
174 #ifdef ALLOW_AUTODIFF_TAMC
175 C Initialise for TAF
176 DO j=1-Oly,sNy+Oly
177 DO i=1-Olx,sNx+Olx
178 c iceFld(i,j) = 0. _d 0
179 gFld(i,j) = 0. _d 0
180 ENDDO
181 ENDDO
182 #endif /* ALLOW_AUTODIFF_TAMC */
183
184 DO j=1-OLy,sNy+OLy
185 DO i=1-OLx,sNx+OLx
186 HEFFNM1(i,j,bi,bj) = HEFF(i,j,bi,bj)
187 AREANM1(i,j,bi,bj) = AREA(i,j,bi,bj)
188 recip_heff(i,j) = 1. _d 0
189 ENDDO
190 ENDDO
191
192 C- Calculate "volume transports" through tracer cell faces.
193 DO j=1-Oly,sNy+Oly
194 DO i=1-Olx,sNx+Olx
195 uTrans(i,j) = uc(i,j,bi,bj)*xA(i,j,bi,bj)
196 vTrans(i,j) = vc(i,j,bi,bj)*yA(i,j,bi,bj)
197 ENDDO
198 ENDDO
199
200 C-- Effective Thickness (Volume)
201 IF ( SEAICEadvHeff ) THEN
202 CALL SEAICE_ADVECTION(
203 I GAD_HEFF, SEAICEadvSchHeff,
204 I uc(1-OLx,1-OLy,bi,bj), vc(1-OLx,1-OLy,bi,bj),
205 I uTrans, vTrans, HEFF(1-OLx,1-OLy,bi,bj), recip_heff,
206 O gFld, afx, afy,
207 I bi, bj, myTime, myIter, myThid )
208 IF ( SEAICEdiffKhHeff .GT. 0. _d 0 ) THEN
209 C- Add tendency due to diffusion
210 CALL SEAICE_DIFFUSION(
211 I GAD_HEFF, SEAICEdiffKhHeff, ONE,
212 I HEFF(1-OLx,1-OLy,bi,bj), HEFFM,
213 I xA(1-OLx,1-OLy,bi,bj), yA(1-OLx,1-OLy,bi,bj),
214 U gFld,
215 I bi, bj, myTime, myIter, myThid )
216 ENDIF
217 C now do the "explicit" time step
218 DO j=1,sNy
219 DO i=1,sNx
220 HEFF(i,j,bi,bj) = HEFFM(i,j,bi,bj) * (
221 & HEFF(i,j,bi,bj) + SEAICE_deltaTtherm * gFld(i,j)
222 & )
223 ENDDO
224 ENDDO
225 ENDIF
226
227 C-- Fractional area
228 IF ( SEAICEadvArea ) THEN
229 CALL SEAICE_ADVECTION(
230 I GAD_AREA, SEAICEadvSchArea,
231 I uc(1-OLx,1-OLy,bi,bj), vc(1-OLx,1-OLy,bi,bj),
232 I uTrans, vTrans, AREA(1-OLx,1-OLy,bi,bj), recip_heff,
233 O gFld, afx, afy,
234 I bi, bj, myTime, myIter, myThid )
235 IF ( SEAICEdiffKhArea .GT. 0. _d 0 ) THEN
236 C- Add tendency due to diffusion
237 CALL SEAICE_DIFFUSION(
238 I GAD_AREA, SEAICEdiffKhArea, ONE,
239 I AREA(1-OLx,1-OLy,bi,bj), HEFFM,
240 I xA(1-OLx,1-OLy,bi,bj), yA(1-OLx,1-OLy,bi,bj),
241 U gFld,
242 I bi, bj, myTime, myIter, myThid )
243 ENDIF
244 C now do the "explicit" time step
245 DO j=1,sNy
246 DO i=1,sNx
247 AREA(i,j,bi,bj) = HEFFM(i,j,bi,bj) * (
248 & AREA(i,j,bi,bj) + SEAICE_deltaTtherm * gFld(i,j)
249 & )
250 ENDDO
251 ENDDO
252 ENDIF
253
254 C-- Effective Snow Thickness (Volume)
255 IF ( SEAICEadvSnow ) THEN
256 CALL SEAICE_ADVECTION(
257 I GAD_SNOW, SEAICEadvSchSnow,
258 I uc(1-OLx,1-OLy,bi,bj), vc(1-OLx,1-OLy,bi,bj),
259 I uTrans, vTrans, HSNOW(1-OLx,1-OLy,bi,bj), recip_heff,
260 O gFld, afx, afy,
261 I bi, bj, myTime, myIter, myThid )
262 IF ( SEAICEdiffKhSnow .GT. 0. _d 0 ) THEN
263 C-- Add tendency due to diffusion
264 CALL SEAICE_DIFFUSION(
265 I GAD_SNOW, SEAICEdiffKhSnow, ONE,
266 I HSNOW(1-OLx,1-OLy,bi,bj), HEFFM,
267 I xA(1-OLx,1-OLy,bi,bj), yA(1-OLx,1-OLy,bi,bj),
268 U gFld,
269 I bi, bj, myTime, myIter, myThid )
270 ENDIF
271 C now do the "explicit" time step
272 DO j=1,sNy
273 DO i=1,sNx
274 HSNOW(i,j,bi,bj) = HEFFM(i,j,bi,bj) * (
275 & HSNOW(i,j,bi,bj) + SEAICE_deltaTtherm * gFld(i,j)
276 & )
277 ENDDO
278 ENDDO
279 ENDIF
280
281 #ifdef SEAICE_VARIABLE_SALINITY
282 C-- Effective Sea Ice Salinity (Mass of salt)
283 IF ( SEAICEadvSalt ) THEN
284 CALL SEAICE_ADVECTION(
285 I GAD_SALT, SEAICEadvSchSalt,
286 I uc(1-OLx,1-OLy,bi,bj), vc(1-OLx,1-OLy,bi,bj),
287 I uTrans, vTrans, HSALT(1-OLx,1-OLy,bi,bj), recip_heff,
288 O gFld, afx, afy,
289 I bi, bj, myTime, myIter, myThid )
290 IF ( SEAICEdiffKhSalt .GT. 0. _d 0 ) THEN
291 C-- Add tendency due to diffusion
292 CALL SEAICE_DIFFUSION(
293 I GAD_SALT, SEAICEdiffKhSalt, ONE,
294 I HSALT(1-OLx,1-OLy,bi,bj), HEFFM,
295 I xA(1-OLx,1-OLy,bi,bj), yA(1-OLx,1-OLy,bi,bj),
296 U gFld,
297 I bi, bj, myTime, myIter, myThid )
298 ENDIF
299 C now do the "explicit" time step
300 DO j=1,sNy
301 DO i=1,sNx
302 HSALT(i,j,bi,bj) = HEFFM(i,j,bi,bj) * (
303 & HSALT(i,j,bi,bj) + SEAICE_deltaTtherm * gFld(i,j)
304 & )
305 ENDDO
306 ENDDO
307 ENDIF
308 #endif /* SEAICE_VARIABLE_SALINITY */
309
310 #ifdef ALLOW_SITRACER
311 C-- Sea Ice Tracers
312 DO iTr = 1, SItrMaxNum
313 IF ( (SEAICEadvHEFF.AND.(SItrMate(iTr).EQ.'HEFF')).OR.
314 & (SEAICEadvAREA.AND.(SItrMate(iTr).EQ.'AREA')) ) THEN
315 C-- scale to effective value
316 IF (SItrMate(iTr).EQ.'HEFF') THEN
317 SEAICEadvSchSItr=SEAICEadvSchHEFF
318 SEAICEdiffKhSItr=SEAICEdiffKhHEFF
319 DO j=1-Oly,sNy+Oly
320 DO i=1-Olx,sNx+Olx
321 SItrExt(i,j,bi,bj) = HEFFM(i,j,bi,bj) *
322 & SItracer(i,j,bi,bj,iTr) * HEFFNM1(i,j,bi,bj)
323 ENDDO
324 ENDDO
325 c TAF? ELSEIF (SItrMate(iTr).EQ.'AREA') THEN
326 ELSE
327 SEAICEadvSchSItr=SEAICEadvSchAREA
328 SEAICEdiffKhSItr=SEAICEdiffKhAREA
329 DO j=1-Oly,sNy+Oly
330 DO i=1-Olx,sNx+Olx
331 SItrExt(i,j,bi,bj) = HEFFM(i,j,bi,bj) *
332 & SItracer(i,j,bi,bj,iTr) * AREANM1(i,j,bi,bj)
333 ENDDO
334 ENDDO
335 ENDIF
336 C-- store a couple things
337 DO j=1-Oly,sNy+Oly
338 DO i=1-Olx,sNx+Olx
339 #ifdef ALLOW_SITRACER_ADVCAP
340 C-- store previous value for spurious maxima treament
341 SItrPrev(i,j,bi,bj)=SItracer(i,j,bi,bj,iTr)
342 #endif
343 #ifdef ALLOW_SITRACER_DIAG
344 diagArray(I,J,2+(iTr-1)*5) = SItrExt(i,j,bi,bj)
345 #endif
346 ENDDO
347 ENDDO
348 C-- compute advective tendency
349 CALL SEAICE_ADVECTION(
350 I GAD_SITR+iTr-1, SEAICEadvSchSItr,
351 I uc(1-OLx,1-OLy,bi,bj), vc(1-OLx,1-OLy,bi,bj),
352 I uTrans, vTrans, SItrExt(1-OLx,1-OLy,bi,bj),
353 I recip_heff,
354 O gFld, afx, afy,
355 I bi, bj, myTime, myIter, myThid )
356 IF ( SEAICEdiffKhHeff .GT. 0. _d 0 ) THEN
357 C-- add diffusive tendency
358 CALL SEAICE_DIFFUSION(
359 I GAD_SITR+iTr-1, SEAICEdiffKhSItr, ONE,
360 I SItrExt(1-OLx,1-OLy,bi,bj), HEFFM,
361 I xA(1-OLx,1-OLy,bi,bj), yA(1-OLx,1-OLy,bi,bj),
362 U gFld,
363 I bi, bj, myTime, myIter, myThid )
364 ENDIF
365 C-- apply tendency
366 DO j=1,sNy
367 DO i=1,sNx
368 SItrExt(i,j,bi,bj) = HEFFM(i,j,bi,bj) * (
369 & SItrExt(i,j,bi,bj) + SEAICE_deltaTtherm * gFld(i,j) )
370 ENDDO
371 ENDDO
372 C-- scale back to actual value, or move effective value to ocean bucket
373 IF (SItrMate(iTr).EQ.'HEFF') THEN
374 DO j=1,sNy
375 DO i=1,sNx
376 if (HEFF(I,J,bi,bj).GE.siEps) then
377 SItracer(i,j,bi,bj,iTr)=SItrExt(i,j,bi,bj)/HEFF(I,J,bi,bj)
378 SItrBucket(i,j,bi,bj,iTr)=0. _d 0
379 else
380 SItracer(i,j,bi,bj,iTr)=0. _d 0
381 SItrBucket(i,j,bi,bj,iTr)=SItrExt(i,j,bi,bj)
382 endif
383 #ifdef ALLOW_SITRACER_ADVCAP
384 c hack to try avoid 'spontaneous generation' of maxima, which supposedly would
385 c occur less frequently if we advected SItr with uXheff instead SItrXheff with u
386 tmpscal1=max(SItrPrev(i,j,bi,bj),
387 & SItrPrev(i+1,j,bi,bj),SItrPrev(i-1,j,bi,bj),
388 & SItrPrev(i,j+1,bi,bj),SItrPrev(i,j-1,bi,bj))
389 tmpscal2=MAX(ZERO,SItracer(i,j,bi,bj,iTr)-tmpscal1)
390 SItracer(i,j,bi,bj,iTr)=SItracer(i,j,bi,bj,iTr)-tmpscal2
391 SItrBucket(i,j,bi,bj,iTr)=SItrBucket(i,j,bi,bj,iTr)
392 & +tmpscal2*HEFF(I,J,bi,bj)
393 #endif
394 c treat case of potential negative value
395 if (HEFF(I,J,bi,bj).GE.siEps) then
396 tmpscal1=MIN(0. _d 0,SItracer(i,j,bi,bj,iTr))
397 SItracer(i,j,bi,bj,iTr)=SItracer(i,j,bi,bj,iTr)-tmpscal1
398 SItrBucket(i,j,bi,bj,iTr)=SItrBucket(i,j,bi,bj,iTr)
399 & +HEFF(I,J,bi,bj)*tmpscal1
400 endif
401 #ifdef ALLOW_SITRACER_DIAG
402 diagArray(I,J,1+(iTr-1)*5)= - SItrBucket(i,j,bi,bj,iTr)
403 & *HEFFM(I,J,bi,bj)/SEAICE_deltaTtherm*SEAICE_rhoIce
404 tmpscal1= ( HEFF(I,J,bi,bj)*SItracer(i,j,bi,bj,iTr)
405 & + SItrBucket(i,j,bi,bj,iTr) )*HEFFM(I,J,bi,bj)
406 diagArray(I,J,2+(iTr-1)*5)= tmpscal1-diagArray(I,J,2+(iTr-1)*5)
407 diagArray(I,J,3+(iTr-1)*5)=HEFFM(i,j,bi,bj) *
408 & SEAICE_deltaTtherm * gFld(i,j)
409 #endif
410 ENDDO
411 ENDDO
412 c TAF? ELSEIF (SItrMate(iTr).EQ.'AREA') THEN
413 ELSE
414 DO j=1,sNy
415 DO i=1,sNx
416 if (AREA(I,J,bi,bj).GE.areaMin) then
417 SItracer(i,j,bi,bj,iTr)=SItrExt(i,j,bi,bj)/AREA(I,J,bi,bj)
418 else
419 SItracer(i,j,bi,bj,iTr)=0. _d 0
420 endif
421 SItrBucket(i,j,bi,bj,iTr)=0. _d 0
422 #ifdef ALLOW_SITRACER_ADVCAP
423 tmpscal1=max(SItrPrev(i,j,bi,bj),
424 & SItrPrev(i+1,j,bi,bj),SItrPrev(i-1,j,bi,bj),
425 & SItrPrev(i,j+1,bi,bj),SItrPrev(i,j-1,bi,bj))
426 tmpscal2=MAX(ZERO,SItracer(i,j,bi,bj,iTr)-tmpscal1)
427 SItracer(i,j,bi,bj,iTr)=SItracer(i,j,bi,bj,iTr)-tmpscal2
428 #endif
429 c treat case of potential negative value
430 if (AREA(I,J,bi,bj).GE.areaMin) then
431 tmpscal1=MIN(0. _d 0,SItracer(i,j,bi,bj,iTr))
432 SItracer(i,j,bi,bj,iTr)=SItracer(i,j,bi,bj,iTr)-tmpscal1
433 endif
434 #ifdef ALLOW_SITRACER_DIAG
435 diagArray(I,J,1+(iTr-1)*5)= 0. _d 0
436 diagArray(I,J,2+(iTr-1)*5)= - diagArray(I,J,2+(iTr-1)*5)
437 & + AREA(I,J,bi,bj)*SItracer(i,j,bi,bj,iTr)*HEFFM(I,J,bi,bj)
438 diagArray(I,J,3+(iTr-1)*5)=HEFFM(i,j,bi,bj) *
439 & SEAICE_deltaTtherm * gFld(i,j)
440 #endif
441 ENDDO
442 ENDDO
443 ENDIF
444 C--
445 ENDIF
446 ENDDO
447 #ifdef ALLOW_SITRACER_DIAG
448 CALL DIAGNOSTICS_FILL(DIAGarray,'UDIAG2 ',0,Nr,2,bi,bj,myThid)
449 #endif
450 #endif /* ALLOW_SITRACER */
451
452 #ifdef SEAICE_AGE
453 C-- Sea Ice Age
454 IF ( SEAICEadvAge ) THEN
455 DO iTracer = 1, SEAICE_num
456 C--
457 CALL SEAICE_ADVECTION(
458 I GAD_SITR+SItrMaxNum+iTracer-1, SEAICEadvSchAge,
459 I uc(1-OLx,1-OLy,bi,bj), vc(1-OLx,1-OLy,bi,bj),
460 I uTrans, vTrans, IceAgeTr(1-OLx,1-OLy,bi,bj,iTracer),
461 I recip_heff,
462 O gFld, afx, afy,
463 I bi, bj, myTime, myIter, myThid )
464 IF ( SEAICEdiffKhAge .GT. 0. _d 0 ) THEN
465 C-- Add tendency due to diffusion
466 CALL SEAICE_DIFFUSION(
467 I GAD_SITR+SItrMaxNum+iTracer-1, SEAICEdiffKhAge, ONE,
468 I IceAgeTr(1-OLx,1-OLy,bi,bj,iTracer), HEFFM,
469 I xA(1-OLx,1-OLy,bi,bj), yA(1-OLx,1-OLy,bi,bj),
470 U gFld,
471 I bi, bj, myTime, myIter, myThid )
472 ENDIF
473 C now do the "explicit" time step
474 DO j=1,sNy
475 DO i=1,sNx
476 IceAgeTr(i,j,bi,bj,iTracer) = HEFFM(i,j,bi,bj) * (
477 & IceAgeTr(i,j,bi,bj,iTracer)
478 & + SEAICE_deltaTtherm * gFld(i,j)
479 & )
480 ENDDO
481 ENDDO
482 C--
483 ENDDO
484 ENDIF
485 #endif /* SEAICE_AGE */
486
487 C--- end bi,bj loops
488 ENDDO
489 ENDDO
490
491 ELSE
492 C-- if not multiDimAdvection
493
494 #ifdef ALLOW_AUTODIFF_TAMC
495 CADJ STORE uc = comlev1, key = ikey_dynamics, kind=isbyte
496 CADJ STORE vc = comlev1, key = ikey_dynamics, kind=isbyte
497 #endif /* ALLOW_AUTODIFF_TAMC */
498
499 IF ( SEAICEadvHEff ) THEN
500 CALL ADVECT( uc, vc, hEff, hEffNm1, HEFFM, myThid )
501 IF ( SEAICEdiffKhHeff .GT. 0. _d 0 ) THEN
502 C- Add tendency due to diffusion
503 DO bj=myByLo(myThid),myByHi(myThid)
504 DO bi=myBxLo(myThid),myBxHi(myThid)
505 CALL SEAICE_DIFFUSION(
506 I GAD_HEFF, SEAICEdiffKhHeff, SEAICE_deltaTtherm,
507 I hEffNm1(1-OLx,1-OLy,bi,bj), HEFFM,
508 I xA(1-OLx,1-OLy,bi,bj), yA(1-OLx,1-OLy,bi,bj),
509 U HEFF(1-OLx,1-OLy,bi,bj),
510 I bi, bj, myTime, myIter, myThid )
511 ENDDO
512 ENDDO
513 ENDIF
514 ENDIF
515 IF ( SEAICEadvArea ) THEN
516 CALL ADVECT( uc, vc, area, areaNm1, HEFFM, myThid )
517 IF ( SEAICEdiffKhArea .GT. 0. _d 0 ) THEN
518 C- Add tendency due to diffusion
519 DO bj=myByLo(myThid),myByHi(myThid)
520 DO bi=myBxLo(myThid),myBxHi(myThid)
521 CALL SEAICE_DIFFUSION(
522 I GAD_AREA, SEAICEdiffKhArea, SEAICE_deltaTtherm,
523 I AreaNm1(1-OLx,1-OLy,bi,bj), HEFFM,
524 I xA(1-OLx,1-OLy,bi,bj), yA(1-OLx,1-OLy,bi,bj),
525 U Area(1-OLx,1-OLy,bi,bj),
526 I bi, bj, myTime, myIter, myThid )
527 ENDDO
528 ENDDO
529 ENDIF
530 ENDIF
531 IF ( SEAICEadvSnow ) THEN
532 CALL ADVECT( uc, vc, HSNOW, fldNm1, HEFFM, myThid )
533 IF ( SEAICEdiffKhSnow .GT. 0. _d 0 ) THEN
534 C- Add tendency due to diffusion
535 DO bj=myByLo(myThid),myByHi(myThid)
536 DO bi=myBxLo(myThid),myBxHi(myThid)
537 CALL SEAICE_DIFFUSION(
538 I GAD_SNOW, SEAICEdiffKhSnow, SEAICE_deltaTtherm,
539 I fldNm1(1-OLx,1-OLy,bi,bj), HEFFM,
540 I xA(1-OLx,1-OLy,bi,bj), yA(1-OLx,1-OLy,bi,bj),
541 U HSNOW(1-OLx,1-OLy,bi,bj),
542 I bi, bj, myTime, myIter, myThid )
543 ENDDO
544 ENDDO
545 ENDIF
546 ENDIF
547
548 #ifdef SEAICE_VARIABLE_SALINITY
549 IF ( SEAICEadvSalt ) THEN
550 CALL ADVECT( uc, vc, HSALT, fldNm1, HEFFM, myThid )
551 IF ( SEAICEdiffKhSalt .GT. 0. _d 0 ) THEN
552 C- Add tendency due to diffusion
553 DO bj=myByLo(myThid),myByHi(myThid)
554 DO bi=myBxLo(myThid),myBxHi(myThid)
555 CALL SEAICE_DIFFUSION(
556 I GAD_SALT, SEAICEdiffKhSalt, SEAICE_deltaTtherm,
557 I fldNm1(1-OLx,1-OLy,bi,bj), HEFFM,
558 I xA(1-OLx,1-OLy,bi,bj), yA(1-OLx,1-OLy,bi,bj),
559 U HSALT(1-OLx,1-OLy,bi,bj),
560 I bi, bj, myTime, myIter, myThid )
561 ENDDO
562 ENDDO
563 ENDIF
564 ENDIF
565 #endif /* SEAICE_VARIABLE_SALINITY */
566
567 #ifdef SEAICE_AGE
568 IF ( SEAICEadvAge ) THEN
569 DO iTracer = 1, SEAICE_num
570 CALL ADVECT( uc, vc, iceAgeTr(1-Olx,1-Oly,1,1,iTracer),
571 & fldNm1, HEFFM, myThid )
572 IF ( SEAICEdiffKhAge .GT. 0. _d 0 ) THEN
573 C-- Add tendency due to diffusion
574 DO bj=myByLo(myThid),myByHi(myThid)
575 DO bi=myBxLo(myThid),myBxHi(myThid)
576 CALL SEAICE_DIFFUSION( GAD_SITR+SItrMaxNum+iTracer-1,
577 I SEAICEdiffKhAge, SEAICE_deltaTtherm,
578 I fldNm1(1-OLx,1-OLy,bi,bj), HEFFM,
579 I xA(1-OLx,1-OLy,bi,bj), yA(1-OLx,1-OLy,bi,bj),
580 U iceAgeTr(1-Olx,1-Oly,bi,bj,iTracer),
581 I bi, bj, myTime, myIter, myThid )
582 ENDDO
583 ENDDO
584 ENDIF
585 ENDDO
586 ENDIF
587 #endif /* SEAICE_AGE */
588
589 C-- end if multiDimAdvection
590 ENDIF
591
592 #ifdef ALLOW_AUTODIFF_TAMC
593 CADJ STORE AREA = comlev1, key = ikey_dynamics, kind=isbyte
594 #endif
595 IF ( .NOT. usePW79thermodynamics ) THEN
596 C Hiblers "ridging function": Do it now if not in seaice_growth
597 C in principle we should add a "real" ridging function here (or
598 C somewhere after doing the advection)
599 DO bj=myByLo(myThid),myByHi(myThid)
600 DO bi=myBxLo(myThid),myBxHi(myThid)
601 DO j=1-Oly,sNy+Oly
602 DO i=1-Olx,sNx+Olx
603 #ifdef SEAICE_AGE
604 C avoid ridging of sea ice age (at this point ridged ice means AREA > 1)
605 DO iTracer = 1, SEAICE_num
606 IceAgeTr(i,j,bi,bj,iTracer) = IceAgeTr(i,j,bi,bj,iTracer)
607 & / MAX(ONE,AREA(i,j,bi,bj))
608 ENDDO
609 #endif /* SEAICE_AGE */
610 AREA(I,J,bi,bj) = MIN(ONE,AREA(I,J,bi,bj))
611 ENDDO
612 ENDDO
613 ENDDO
614 ENDDO
615 #ifdef SEAICE_AGE
616 C Sources and sinks for sea ice age (otherwise added in seaice_growth)
617 IF ( .TRUE. ) THEN
618 DO iTracer = 1, SEAICE_num
619 DO bj=myByLo(myThid),myByHi(myThid)
620 DO bi=myBxLo(myThid),myBxHi(myThid)
621 DO j=1,sNy
622 DO i=1,sNx
623 cph(
624 cph-- why is this code still here?
625 cph-- probably wrong for thickness-weighted age(?)
626 IF ( AREA(i,j,bi,bj) .GT. 0.15 ) THEN
627 IceAgeTr(i,j,bi,bj,iTracer) = IceAgeTr(i,j,bi,bj,iTracer)
628 & + AREA(i,j,bi,bj) * SEAICE_deltaTtherm
629 ELSE
630 IceAgeTr(i,j,bi,bj,iTracer) = ZERO
631 ENDIF
632 cph)
633 ENDDO
634 ENDDO
635 ENDDO
636 ENDDO
637 ENDDO
638 ENDIF
639 #endif /* SEAICE_AGE */
640 ENDIF
641
642 RETURN
643 END

  ViewVC Help
Powered by ViewVC 1.1.22