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

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

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


Revision 1.14 - (show annotations) (download)
Fri Jun 8 14:41:04 2007 UTC (17 years ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f
Changes since 1.13: +3 -4 lines
Change limiting behaviour of deltaC, pressC for stable adjoint.
(Martin lured me into code changes that will require changes of output)

1 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_evp.F,v 1.13 2007/06/06 14:26:32 mlosch Exp $
2 C $Name: $
3
4 #include "SEAICE_OPTIONS.h"
5
6 CStartOfInterface
7 SUBROUTINE SEAICE_EVP( myTime, myIter, myThid )
8 C /==========================================================\
9 C | SUBROUTINE SEAICE_EVP |
10 C | o Ice dynamics using an EVP solver following |
11 C | E. C. Hunke and J. K. Dukowicz. An |
12 C | Elastic-Viscous-Plastic Model for Sea Ice Dynamics, |
13 C | J. Phys. Oceanogr., 27, 1849-1867 (1997). |
14 C |==========================================================|
15 C | written by Martin Losch, March 2006 |
16 C \==========================================================/
17 IMPLICIT NONE
18
19 C === Global variables ===
20 #include "SIZE.h"
21 #include "EEPARAMS.h"
22 #include "PARAMS.h"
23 #include "GRID.h"
24 #include "SEAICE.h"
25 #include "SEAICE_PARAMS.h"
26
27 #ifdef ALLOW_AUTODIFF_TAMC
28 # include "tamc.h"
29 #endif
30
31 C === Routine arguments ===
32 C myTime - Simulation time
33 C myIter - Simulation timestep number
34 C myThid - Thread no. that called this routine.
35 _RL myTime
36 INTEGER myIter
37 INTEGER myThid
38 CEndOfInterface
39
40 #if ( defined (SEAICE_CGRID) && \
41 defined (SEAICE_ALLOW_EVP) && \
42 defined (SEAICE_ALLOW_DYNAMICS) )
43
44 C === Local variables ===
45 C i,j,bi,bj - Loop counters
46 C nEVPstep - number of timesteps within the EVP solver
47 C iEVPstep - Loop counter
48 C SIN/COSWAT - sine/cosine of turning angle
49 C recip_evp_tau - inverse of EVP relaxation/damping timescale
50 C ecc2 - eccentricity squared
51 C e11,e12,e22 - components of strain rate tensor
52 C seaice_div - divergence strain rates at C-points times P
53 C /divided by Delta minus 1
54 C seaice_tension- tension strain rates at C-points times P
55 C /divided by Delta
56 C seaice_shear - shear strain rates, defined at Z-points times P
57 C /divided by Delta
58 C sig11, sig22 - sum and difference of diagonal terms of stress tensor
59
60 INTEGER i, j, bi, bj
61 INTEGER nEVPstep, iEVPstep
62 INTEGER ikeyloc
63 #ifndef ALLOW_AUTODIFF_TAMC
64 integer nEVPstepMax
65 #endif
66
67 _RL SINWAT, COSWAT
68 _RL TEMPVAR, ecc2, recip_ecc2, recip_evp_tau
69
70 _RL e11 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
71 _RL e22 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
72 _RL e12 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
73 _RL seaice_div (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
74 _RL seaice_tension(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
75 _RL seaice_shear (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
76 _RL sig11 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
77 _RL sig22 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
78 C auxilliary variables
79 _RL e11C, e22C, e12C, deltaC, deltaCreg, pressC, zetaC
80 _RL e11Z, e22Z, e12Z, deltaZ, deltaZreg, pressZ, zetaZ
81 _RL denom1, denom2, fac
82
83 C-- introduce turning angles
84 SINWAT=SIN(SEAICE_waterTurnAngle*deg2rad)
85 COSWAT=COS(SEAICE_waterTurnAngle*deg2rad)
86
87 C abbreviation eccentricity squared
88 ecc2=SEAICE_eccen**2
89 recip_ecc2 = 0. _d 0
90 IF ( ecc2 .NE. 0. _d 0 ) recip_ecc2=ONE/ecc2
91 C determine number of interal time steps
92 nEVPstep = INT(SEAICE_deltaTdyn/SEAICE_deltaTevp)
93 C inverse relaxation/damping time scale
94 recip_evp_tau = 0. _d 0
95 IF ( SEAICE_evpTauRelax .GT. 0. _d 0 )
96 & recip_evp_tau=1. _d 0/SEAICE_evpTauRelax
97 denom1 = 1. _d 0
98 & / (1. _d 0 + 0.5 _d 0 *SEAICE_deltaTevp*recip_evp_tau)
99 denom2 = 1. _d 0
100 & / (1. _d 0 + 0.5 _d 0 *SEAICE_deltaTevp*recip_evp_tau*ecc2)
101 #ifndef ALLOW_AUTODIFF_TAMC
102 nEVPstepMax = nEVPstep
103 #endif
104
105 DO bj=myByLo(myThid),myByHi(myThid)
106 DO bi=myBxLo(myThid),myBxHi(myThid)
107 DO j=1-Oly,sNy+Oly
108 DO i=1-Olx,sNx+Olx
109 C save last external time step (useless, but consistent with
110 C VP-solver)
111 uIce (I,J,2,bi,bj) = uIce(I,J,1,bi,bj)
112 vIce (I,J,2,bi,bj) = vIce(I,J,1,bi,bj)
113 C use u/vIceC as work arrays: copy previous time step to u/vIceC
114 uIceC(I,J,bi,bj) = uIce(I,J,1,bi,bj)
115 vIceC(I,J,bi,bj) = vIce(I,J,1,bi,bj)
116 c initialise strain rates
117 e11 (I,J,bi,bj) = 0. _d 0
118 e22 (I,J,bi,bj) = 0. _d 0
119 e12 (I,J,bi,bj) = 0. _d 0
120 ENDDO
121 ENDDO
122 ENDDO
123 ENDDO
124 C damping constraint (Hunke, J.Comp.Phys.,2001)
125 IF ( SEAICE_evpDampC .GT. 0. _d 0 ) THEN
126 fac = HALF * SEAICE_evpDampC * SEAICE_evpTauRelax
127 & /SEAICE_deltaTevp**2
128 DO bj=myByLo(myThid),myByHi(myThid)
129 DO bi=myBxLo(myThid),myBxHi(myThid)
130 DO j=1-Oly,sNy+Oly
131 DO i=1-Olx,sNx+Olx
132 zMax (I,J,bi,bj) = _rA(I,J,bi,bj) * fac
133 ENDDO
134 ENDDO
135 ENDDO
136 ENDDO
137 ENDIF
138 C
139 C start of the main time loop
140 DO iEVPstep = 1, nEVPstepMax
141 IF (iEVPstep.LE.nEVPstep) THEN
142 C
143 #ifdef ALLOW_AUTODIFF_TAMC
144 ikeyloc = iEVPstep +
145 & (ikey_dynamics-1)*nEVPstepMax
146 CADJ STORE uicec = comlev1_evp,
147 CADJ & key = ikeyloc, byte = isbyte
148 CADJ STORE vicec = comlev1_evp,
149 CADJ & key = ikeyloc, byte = isbyte
150 CADJ STORE seaice_sigma1 = comlev1_evp,
151 CADJ & key = ikeyloc, byte = isbyte
152 CADJ STORE seaice_sigma2 = comlev1_evp,
153 CADJ & key = ikeyloc, byte = isbyte
154 CADJ STORE seaice_sigma12 = comlev1_evp,
155 CADJ & key = ikeyloc, byte = isbyte
156 #endif /* ALLOW_AUTODIFF_TAMC */
157 C
158 C first calculate strain rates and bulk moduli/viscosities
159 C
160 CALL SEAICE_CALC_STRAINRATES(
161 I uIceC, vIceC,
162 O e11, e22, e12,
163 I myThid )
164
165 DO bj=myByLo(myThid),myByHi(myThid)
166 DO bi=myBxLo(myThid),myBxHi(myThid)
167 DO j=1-Oly,sNy+Oly
168 DO i=1-Olx,sNx+Olx
169 seaice_div (I,J) = 0. _d 0
170 seaice_tension(I,J) = 0. _d 0
171 seaice_shear (I,J) = 0. _d 0
172 ENDDO
173 ENDDO
174 DO j=0,sNy+1
175 DO i=0,sNx+1
176 C average strain rates to Z and C points
177 e11C = e11(i,j,bi,bj)
178 e22C = e22(i,j,bi,bj)
179 e12C = 0.25 _d 0
180 & * ( e12(I,J ,bi,bj) + e12(I+1,J ,bi,bj)
181 & + e12(I,J+1,bi,bj) + e12(I+1,J+1,bi,bj) )
182 e11Z = 0.25 _d 0
183 & * ( e11(I,J ,bi,bj) + e11(I-1,J ,bi,bj)
184 & + e11(I,J-1,bi,bj) + e11(I-1,J-1,bi,bj) )
185 e22Z = 0.25 _d 0
186 & * ( e22(I,J ,bi,bj) + e22(I-1,J ,bi,bj)
187 & + e22(I,J-1,bi,bj) + e22(I-1,J-1,bi,bj) )
188 e12Z = e12(i,j,bi,bj)
189 deltaC = (e11C**2+e22C**2)*(ONE+recip_ecc2)
190 & + 4. _d 0*recip_ecc2*e12C**2
191 & + 2. _d 0*e11C*e22C*(ONE-recip_ecc2)
192 deltaCreg = SQRT(MAX(deltaC,SEAICE_EPS_SQ))
193 deltaZ = (e11Z**2+e22Z**2)*(ONE+recip_ecc2)
194 & + 4. _d 0*recip_ecc2*e12Z**2
195 & + 2. _d 0*e11Z*e22Z*(ONE-recip_ecc2)
196 deltaZreg = SQRT(MAX(deltaZ,SEAICE_EPS_SQ))
197 #ifdef ALLOW_AUTODIFF_TAMC
198 C avoid sqrt of 0
199 IF ( deltaC .GT. 0. _d 0 ) deltaC = SQRT(deltaC)
200 IF ( deltaZ .GT. 0. _d 0 ) deltaZ = SQRT(deltaZ)
201 #else
202 deltaC = SQRT(deltaC)
203 deltaZ = SQRT(deltaZ)
204 #endif /* ALLOW_AUTODIFF_TAMC */
205 C modify pressure (copied from seaice_calc_viscosities)
206 zetaC = HALF*press0(I,J,bi,bj)/deltaCreg
207 zetaC = MIN(zMax(I,J,bi,bj),zetaC)
208 zetaC = MAX(zMin(I,J,bi,bj),zetaC)
209 CML zetaC = zetaC*hEffM(I,J,bi,bj)
210 pressZ = (deltaZ/deltaZreg) * 0.25 _d 0
211 & * ( PRESS0(I,J ,bi,bj) + PRESS0(I-1,J ,bi,bj)
212 & + PRESS0(I,J-1,bi,bj) + PRESS0(I-1,J-1,bi,bj) )
213 zetaZ = HALF/deltaZreg * pressZ
214 zetaZ = MIN(zMax(I,J,bi,bj),zetaZ)
215 zetaZ = MAX(zMin(I,J,bi,bj),zetaZ)
216 pressC = TWO*zetaC*deltaC
217 C Calculate the RHS of the stress equations. Do this now in order to
218 C avoid multiple divisions by Delta
219 C P * ( D_d/Delta - 1 ) = 2*zeta*D_d - P = 2*zeta*D_d - 2*zeta*Delta
220 C P * ( D_t/Delta ) = 2*zeta*D_t
221 C P * ( D_s/Delta ) = 2*zeta*D_s
222 seaice_div (I,J) = (
223 & 2. _d 0 *zetaC*(e11C+e22C) - pressC
224 & ) *hEffM(I,J,bi,bj)
225 seaice_tension(I,J) = 2. _d 0*zetaC*(e11C-e22C)
226 & *hEffM(I,J,bi,bj)
227 seaice_shear (I,J) = 2. _d 0*zetaZ*2. _d 0*e12Z
228 ENDDO
229 ENDDO
230 C
231 C first step stress equations
232 C
233 DO j=0,sNy
234 DO i=0,sNx
235 C sigma1 and sigma2 are computed on C points
236 seaice_sigma1 (I,J,bi,bj) = ( seaice_sigma1 (I,J,bi,bj)
237 & + SEAICE_deltaTevp * 0.5 _d 0 * recip_evp_tau
238 & * seaice_div(I,J)
239 & ) * denom1
240 & *hEffM(I,J,bi,bj)
241 seaice_sigma2 (I,J,bi,bj) = ( seaice_sigma2 (I,J,bi,bj)
242 & + SEAICE_deltaTevp * 0.5 _d 0 * recip_evp_tau
243 & * seaice_tension(I,J)
244 & ) * denom2
245 & *hEffM(I,J,bi,bj)
246 C recover sigma11 and sigma22
247 sig11(I,J) = 0.5 _d 0 *
248 & ( seaice_sigma1(I,J,bi,bj)+seaice_sigma2(I,J,bi,bj) )
249 sig22(I,J) = 0.5 _d 0 *
250 & ( seaice_sigma1(I,J,bi,bj)-seaice_sigma2(I,J,bi,bj) )
251 ENDDO
252 ENDDO
253
254 C sigma12 is computed on Z points
255 DO j=1,sNy+1
256 DO i=1,sNx+1
257 seaice_sigma12(I,J,bi,bj) = ( seaice_sigma12(I,J,bi,bj)
258 & + SEAICE_deltaTevp * 0.25 _d 0 * recip_evp_tau *
259 & seaice_shear(I,J)
260 & ) * denom2
261 ENDDO
262 ENDDO
263 C
264 C compute divergence of stress tensor
265 C
266 DO J=1,sNy
267 DO I=1,sNx
268 stressDivergenceX(I,J,bi,bj) =
269 & ( sig11(I ,J ) * _dyF(I ,J,bi,bj)
270 & - sig11(I-1,J ) * _dyF(I-1,J,bi,bj)
271 & + seaice_sigma12(I,J+1,bi,bj) * _dxV(I,J+1,bi,bj)
272 & - seaice_sigma12(I,J ,bi,bj) * _dxV(I,J ,bi,bj)
273 & ) * recip_rAw(I,J,bi,bj)
274 & -
275 & ( seaice_sigma12(I,J ,bi,bj)
276 & + seaice_sigma12(I,J+1,bi,bj) )
277 & * _tanPhiAtU(I,J,bi,bj) * recip_rSphere
278 & +
279 & ( sig22(I,J) + sig22(I-1,J) ) * 0.5 _d 0
280 & * _tanPhiAtU(I,J,bi,bj) * recip_rSphere
281 C one metric term missing for general curvilinear coordinates
282 stressDivergenceY(I,J,bi,bj) =
283 & ( sig22(I,J ) * _dxF(I,J ,bi,bj)
284 & - sig22(I,J-1) * _dxF(I,J-1,bi,bj)
285 & + seaice_sigma12(I+1,J,bi,bj) * _dyU(I+1,J,bi,bj)
286 & - seaice_sigma12(I ,J,bi,bj) * _dyU(I ,J,bi,bj)
287 & ) * recip_rAs(I,J,bi,bj)
288 & -
289 & ( sig22(I,J) + sig22(I,J-1) ) * 0.5 _d 0
290 & * _tanPhiAtV(I,J,bi,bj) * recip_rSphere
291 C two metric terms missing for general curvilinear coordinates
292 ENDDO
293 ENDDO
294
295 C
296 C set up rhs for stepping the velocity field
297 C
298 DO J=0,sNy
299 DO I=0,sNx
300 C set up non-linear water drag, forcex, forcey
301 TEMPVAR = QUART*(
302 & ( uIceC(I ,J,bi,bj)-GWATX(I ,J,bi,bj)
303 & + uIceC(I+1,J,bi,bj)-GWATX(I+1,J,bi,bj))**2
304 & +(vIceC(I,J ,bi,bj)-GWATY(I,J ,bi,bj)
305 & + vIceC(I,J+1,bi,bj)-GWATY(I,J+1,bi,bj))**2)
306 IF ( TEMPVAR .LE. (QUART/SEAICE_waterDrag)**2 ) THEN
307 DWATN(I,J,bi,bj)=QUART
308 ELSE
309 DWATN(I,J,bi,bj)=SEAICE_waterDrag*SQRT(TEMPVAR)
310 ENDIF
311 DWATN(I,J,bi,bj) = DWATN(I,J,bi,bj) * HEFFM(I,J,bi,bj)
312 C set up symmetric drag
313 DRAGS(I,J,bi,bj) = DWATN(I,J,bi,bj)*COSWAT
314 ENDDO
315 ENDDO
316
317 DO j=1,sNy
318 DO i=1,sNx
319 C set up anti symmetric drag force and add in ice ocean stress
320 C ( remember to average to correct velocity points )
321 FORCEX(I,J,bi,bj)=FORCEX0(I,J,bi,bj)+
322 & 0.5 _d 0 * ( DWATN(I,J,bi,bj)+DWATN(I-1,J,bi,bj) ) *
323 & COSWAT * GWATX(I,J,bi,bj)
324 & - SIGN(SINWAT, _fCori(I,J,bi,bj))* 0.5 _d 0 *
325 & ( DWATN(I ,J,bi,bj) *
326 & 0.5 _d 0 * (GWATY(I ,J ,bi,bj)-vIceC(I ,J ,bi,bj)
327 & +GWATY(I ,J+1,bi,bj)-vIceC(I ,J+1,bi,bj))
328 & + DWATN(I-1,J,bi,bj) *
329 & 0.5 _d 0 * (GWATY(I-1,J ,bi,bj)-vIceC(I-1,J ,bi,bj)
330 & +GWATY(I-1,J+1,bi,bj)-vIceC(I-1,J+1,bi,bj))
331 & )
332 FORCEY(I,J,bi,bj)=FORCEY0(I,J,bi,bj)+
333 & 0.5 _d 0 * ( DWATN(I,J,bi,bj)+DWATN(I,J-1,bi,bj) ) *
334 & COSWAT * GWATY(I,J,bi,bj)
335 & + SIGN(SINWAT, _fCori(I,J,bi,bj)) * 0.5 _d 0 *
336 & ( DWATN(I,J ,bi,bj) *
337 & 0.5 _d 0 * (GWATX(I ,J ,bi,bj)-uIceC(I ,J ,bi,bj)
338 & +GWATX(I+1,J ,bi,bj)-uIceC(I+1,J ,bi,bj))
339 & + DWATN(I,J-1,bi,bj) *
340 & 0.5 _d 0 * (GWATX(I ,J-1,bi,bj)-uIceC(I ,J-1,bi,bj)
341 & +GWATX(I+1,J-1,bi,bj)-uIceC(I+1,J-1,bi,bj))
342 & )
343 C coriols terms
344 FORCEX(I,J,bi,bj)=FORCEX(I,J,bi,bj) + 0.5 _d 0*(
345 & seaiceMassC(I ,J,bi,bj) * _fCori(I ,J,bi,bj)
346 & * 0.5 _d 0*( vIceC(I ,J,bi,bj)+vIceC(I ,J+1,bi,bj) )
347 & + seaiceMassC(I-1,J,bi,bj) * _fCori(I-1,J,bi,bj)
348 & * 0.5 _d 0*( vIceC(I-1,J,bi,bj)+vIceC(I-1,J+1,bi,bj) )
349 & )
350 FORCEY(I,J,bi,bj)=FORCEY(I,J,bi,bj) - 0.5 _d 0*(
351 & seaiceMassC(I,J ,bi,bj) * _fCori(I,J ,bi,bj)
352 & * 0.5 _d 0*( uIceC(I,J ,bi,bj)+uIceC(I+1, J,bi,bj) )
353 & + seaiceMassC(I,J-1,bi,bj) * _fCori(I,J-1,bi,bj)
354 & * 0.5 _d 0*( uIceC(I,J-1,bi,bj)+uIceC(I+1,J-1,bi,bj) )
355 & )
356 ENDDO
357 ENDDO
358 C
359 C step momentum equations with ice-ocean stress term treated implicitly
360 C
361 DO J=1,sNy
362 DO I=1,sNx
363 uIceC(I,J,bi,bj) = seaiceMaskU(I,J,bi,bj) *
364 & ( seaiceMassU(I,J,bi,bj)/SEAICE_deltaTevp
365 & * uIceC(I,J,bi,bj)
366 & + FORCEX(I,J,bi,bj)
367 & + stressDivergenceX(I,J,bi,bj) )
368 & /( 1. _d 0 - seaiceMaskU(I,J,bi,bj)
369 & + seaiceMassU(I,J,bi,bj)/SEAICE_deltaTevp
370 & + 0.5 _d 0*( DRAGS(I,J,bi,bj) + DRAGS(I-1,J,bi,bj) ) )
371 vIceC(I,J,bi,bj) = seaiceMaskV(I,J,bi,bj) *
372 & ( seaiceMassV(I,J,bi,bj)/SEAICE_deltaTevp
373 & * vIceC(I,J,bi,bj)
374 & + FORCEY(I,J,bi,bj)
375 & + stressDivergenceY(I,J,bi,bj) )
376 & /( 1. _d 0 - seaiceMaskV(I,J,bi,bj)
377 & + seaiceMassV(I,J,bi,bj)/SEAICE_deltaTevp
378 & + 0.5 _d 0*( DRAGS(I,J,bi,bj) + DRAGS(I,J-1,bi,bj) ) )
379 ENDDO
380 ENDDO
381 ENDDO
382 ENDDO
383
384 CALL EXCH_UV_XY_RL(uIceC,vIceC,.TRUE.,myThid)
385
386 ENDIF
387 C end of the main time loop
388 ENDDO
389
390 C Copy work arrays and apply masks
391 DO bj=myByLo(myThid),myByHi(myThid)
392 DO bi=myBxLo(myThid),myBxHi(myThid)
393 DO J=1-Oly,sNy+Oly
394 DO I=1-Olx,sNx+Olx
395 uIce(I,J,1,bi,bj)=uIceC(I,J,bi,bj)* _maskW(I,J,1,bi,bj)
396 vIce(I,J,1,bi,bj)=vIceC(I,J,bi,bj)* _maskS(I,J,1,bi,bj)
397 END DO
398 END DO
399 ENDDO
400 ENDDO
401
402 #endif /* SEAICE_ALLOW_DYNAMICS and SEAICE_CGRID and SEAICE_ALLOW_EVP */
403
404 RETURN
405 END

  ViewVC Help
Powered by ViewVC 1.1.22