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

Annotation of /MITgcm/pkg/seaice/seaice_calc_strainrates.F

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


Revision 1.16 - (hide annotations) (download)
Tue Mar 16 19:21:31 2010 UTC (14 years, 6 months ago) by gforget
Branch: MAIN
CVS Tags: checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62m, checkpoint62l
Changes since 1.15: +11 -1 lines
option that is sometimes useful to stabilize seaice
dynamics adjoint computations. In essence, with this option
the ajdoint is approximated to free drift, by reseting
the rheology adjoint variables to zero

1 gforget 1.16 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_calc_strainrates.F,v 1.15 2009/10/23 08:10:16 mlosch Exp $
2 mlosch 1.1 C $Name: $
3    
4     #include "SEAICE_OPTIONS.h"
5    
6     CStartOfInterface
7 jmc 1.8 SUBROUTINE SEAICE_CALC_STRAINRATES(
8 mlosch 1.1 I uFld, vFld,
9 mlosch 1.12 O e11Loc, e22Loc, e12Loc,
10 mlosch 1.14 I iStep, myTime, myIter, myThid )
11 mlosch 1.1 C /==========================================================\
12     C | SUBROUTINE SEAICE_CALC_STRAINRATES |
13     C | o compute strain rates from ice velocities |
14     C |==========================================================|
15     C | written by Martin Losch, Apr 2007 |
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_PARAMS.h"
25 mlosch 1.11 #include "SEAICE.h"
26 mlosch 1.1
27     #ifdef ALLOW_AUTODIFF_TAMC
28     # include "tamc.h"
29     #endif
30    
31     C === Routine arguments ===
32 jmc 1.8 C iStep :: Sub-time-step number
33     C myTime :: Simulation time
34     C myIter :: Simulation timestep number
35     C myThid :: My Thread Id. number
36     INTEGER iStep
37     _RL myTime
38     INTEGER myIter
39 mlosch 1.1 INTEGER myThid
40     C ice velocities
41 mlosch 1.14 _RL uFld (1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
42     _RL vFld (1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
43 mlosch 1.1 C strain rate tensor
44 mlosch 1.12 _RL e11Loc (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
45     _RL e22Loc (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
46     _RL e12Loc (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
47 mlosch 1.1 CEndOfInterface
48    
49     #ifdef SEAICE_CGRID
50     #ifdef SEAICE_ALLOW_DYNAMICS
51     C === Local variables ===
52     C i,j,bi,bj - Loop counters
53     INTEGER i, j, bi, bj
54 mlosch 1.15 C hFacU, hFacV - determine the no-slip boundary condition
55 mlosch 1.2 INTEGER k
56 mlosch 1.11 _RS hFacU, hFacV, noSlipFac
57 mlosch 1.15 C auxillary variables that help writing code that
58     C vectorizes even after TAFization
59     _RL dudx (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
60     _RL dvdy (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
61     _RL dudy (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
62     _RL dvdx (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
63     _RL uave (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
64     _RL vave (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
65 mlosch 1.2
66 mlosch 1.4 k = 1
67 mlosch 1.11 noSlipFac = 0. _d 0
68     IF ( SEAICE_no_slip ) noSlipFac = 1. _d 0
69 mlosch 1.1 C
70 mlosch 1.11 #ifndef SEAICE_OLD_AND_BAD_DISCRETIZATION
71     DO bj=myByLo(myThid),myByHi(myThid)
72     DO bi=myBxLo(myThid),myBxHi(myThid)
73 mlosch 1.15 C abbreviations on C-points, need to do them in separate loops
74     C for vectorization
75 mlosch 1.11 DO j=1-Oly,sNy+Oly-1
76     DO i=1-Olx,sNx+Olx-1
77 mlosch 1.15 dudx(I,J) = _recip_dxF(I,J,bi,bj) *
78 mlosch 1.14 & (uFld(I+1,J,bi,bj)-uFld(I,J,bi,bj))
79 mlosch 1.15 uave(I,J) = 0.5 _d 0 * (uFld(I,J,bi,bj)+uFld(I+1,J,bi,bj))
80     ENDDO
81     ENDDO
82     DO j=1-Oly,sNy+Oly-1
83     DO i=1-Olx,sNx+Olx-1
84     dvdy(I,J) = _recip_dyF(I,J,bi,bj) *
85 mlosch 1.14 & (vFld(I,J+1,bi,bj)-vFld(I,J,bi,bj))
86 mlosch 1.15 vave(I,J) = 0.5 _d 0 * (vFld(I,J,bi,bj)+vFld(I,J+1,bi,bj))
87     ENDDO
88     ENDDO
89     C evaluate strain rates at C-points
90     DO j=1-Oly,sNy+Oly-1
91     DO i=1-Olx,sNx+Olx-1
92     e11Loc(I,J,bi,bj) = dudx(I,J) + vave(I,J) * k2AtC(I,J,bi,bj)
93     e22Loc(I,J,bi,bj) = dvdy(I,J) + uave(I,J) * k1AtC(I,J,bi,bj)
94 mlosch 1.11 ENDDO
95     ENDDO
96 mlosch 1.15 C abbreviations at Z-points, need to do them in separate loops
97     C for vectorization
98     DO j=1-Oly+1,sNy+Oly
99     DO i=1-Olx+1,sNx+Olx
100     dudy(I,J) = ( uFld(I,J,bi,bj) - uFld(I ,J-1,bi,bj) )
101     & * _recip_dyU(I,J,bi,bj)
102     uave(I,J) = 0.5 _d 0 * (uFld(I,J,bi,bj)+uFld(I ,J-1,bi,bj))
103     ENDDO
104     ENDDO
105     DO j=1-Oly+1,sNy+Oly
106     DO i=1-Olx+1,sNx+Olx
107     dvdx(I,J) = ( vFld(I,J,bi,bj) - vFld(I-1,J ,bi,bj) )
108     & * _recip_dxV(I,J,bi,bj)
109     vave(I,J) = 0.5 _d 0 * (vFld(I,J,bi,bj)+vFld(I-1,J ,bi,bj))
110     ENDDO
111     ENDDO
112     C evaluate strain rates at Z-points
113 mlosch 1.11 DO j=1-Oly+1,sNy+Oly
114     DO i=1-Olx+1,sNx+Olx
115     hFacU = _maskW(i,j,k,bi,bj) - _maskW(i,j-1,k,bi,bj)
116     hFacV = _maskS(i,j,k,bi,bj) - _maskS(i-1,j,k,bi,bj)
117 mlosch 1.15 e12Loc(I,J,bi,bj) = 0.5 _d 0 * (
118     & dudy(I,J) + dvdx(I,J)
119     & - k1AtZ(I,J,bi,bj) * vave(I,J)
120     & - k2AtZ(I,J,bi,bj) * uave(I,J)
121 mlosch 1.11 & )
122     & *maskC(I ,J ,k,bi,bj)*maskC(I-1,J ,k,bi,bj)
123     & *maskC(I ,J-1,k,bi,bj)*maskC(I-1,J-1,k,bi,bj)
124     & + 2.0 _d 0 * noSlipFac * (
125 mlosch 1.15 & 2.0 _d 0 * uave(I,J) * _recip_dyU(I,J,bi,bj) * hFacU
126     & + 2.0 _d 0 * vave(I,J) * _recip_dxV(I,J,bi,bj) * hFacV
127 mlosch 1.11 & )
128     C no slip at the boundary implies u(j)+u(j-1)=0 and v(i)+v(i-1)=0
129     C accross the boundary; this is already accomplished by masking so
130     C that the following lines are not necessary
131 mlosch 1.15 c$$$ & - hFacV * k1AtZ(I,J,bi,bj) * vave(I,J)
132     c$$$ & - hFacU * k2AtZ(I,J,bi,bj) * uave(I,J)
133 mlosch 1.11 ENDDO
134     ENDDO
135    
136     ENDDO
137     ENDDO
138     #else
139     C this the old and incomplete discretization, here I also erroneously
140     C used finite-volumes to discretize the strain rates
141 mlosch 1.1 DO bj=myByLo(myThid),myByHi(myThid)
142     DO bi=myBxLo(myThid),myBxHi(myThid)
143 mlosch 1.5 DO j=1-Oly,sNy+Oly-1
144     DO i=1-Olx,sNx+Olx-1
145     C evaluate strain rates
146 mlosch 1.12 e11Loc(I,J,bi,bj) = _recip_dxF(I,J,bi,bj) *
147 mlosch 1.14 & (uFld(I+1,J,bi,bj)-uFld(I,J,bi,bj))
148 mlosch 1.1 & -HALF*
149 mlosch 1.14 & (vFld(I,J,bi,bj)+vFld(I,J+1,bi,bj))
150 mlosch 1.1 & * _tanPhiAtU(I,J,bi,bj)*recip_rSphere
151 mlosch 1.12 e22Loc(I,J,bi,bj) = _recip_dyF(I,J,bi,bj) *
152 mlosch 1.14 & (vFld(I,J+1,bi,bj)-vFld(I,J,bi,bj))
153 mlosch 1.1 C one metric term is missing
154 mlosch 1.5 ENDDO
155     ENDDO
156     DO j=1-Oly+1,sNy+Oly
157     DO i=1-Olx+1,sNx+Olx
158 mlosch 1.12 e12Loc(I,J,bi,bj) = HALF*(
159 mlosch 1.14 & (uFld(I ,J ,bi,bj) * _dxC(I ,J ,bi,bj)
160     & -uFld(I ,J-1,bi,bj) * _dxC(I ,J-1,bi,bj)
161     & +vFld(I ,J ,bi,bj) * _dyC(I ,J ,bi,bj)
162     & -vFld(I-1,J ,bi,bj) * _dyC(I-1,J ,bi,bj))
163 mlosch 1.1 & * recip_rAz(I,J,bi,bj)
164     & +
165 mlosch 1.14 & 0.25 _d 0 * (uFld(I,J,bi,bj)+uFld(I ,J-1,bi,bj))
166 mlosch 1.1 & * ( _tanPhiAtU(I,J,bi,bj) + _tanPhiAtU(I,J-1,bi,bj) )
167     & *recip_rSphere
168     & )
169 mlosch 1.4 & *maskC(I ,J ,k,bi,bj)*maskC(I-1,J ,k,bi,bj)
170     & *maskC(I ,J-1,k,bi,bj)*maskC(I-1,J-1,k,bi,bj)
171 mlosch 1.1 C one metric term is missing
172     ENDDO
173     ENDDO
174 mlosch 1.2 IF ( SEAICE_no_slip ) THEN
175 mlosch 1.12 C no slip boundary conditions apply only to e12Loc
176 mlosch 1.5 DO j=1-Oly+1,sNy+Oly
177     DO i=1-Olx+1,sNx+Olx
178 mlosch 1.2 hFacU = _maskW(i,j,k,bi,bj) - _maskW(i,j-1,k,bi,bj)
179     hFacV = _maskS(i,j,k,bi,bj) - _maskS(i-1,j,k,bi,bj)
180    
181 mlosch 1.12 e12Loc(I,J,bi,bj) = e12Loc(I,J,bi,bj)
182 mlosch 1.10 & + recip_rAz(i,j,bi,bj) * 2. _d 0 *
183 mlosch 1.14 & ( hFacU * ( _dxC(i,j-1,bi,bj)*uFld(i,j ,bi,bj)
184     & + _dxC(i,j, bi,bj)*uFld(i,j-1,bi,bj) )
185     & + hFacV * ( _dyC(i-1,j,bi,bj)*vFld(i ,j,bi,bj)
186     & + _dyC(i, j,bi,bj)*vFld(i-1,j,bi,bj) ) )
187 jmc 1.8 & - hFacU
188 mlosch 1.14 & * 0.25 _d 0 * (uFld(I,J,bi,bj)+uFld(I ,J-1,bi,bj))
189 mlosch 1.2 & * ( _tanPhiAtU(I,J,bi,bj) + _tanPhiAtU(I,J-1,bi,bj) )
190     & *recip_rSphere
191     C one metric term is missing
192     ENDDO
193     ENDDO
194    
195     ENDIF
196 mlosch 1.1 ENDDO
197     ENDDO
198 mlosch 1.11 #endif /* SEAICE_OLD_AND_BAD_DISCRETIZATION */
199 gforget 1.16
200     #ifdef ALLOW_AUTODIFF_TAMC
201     #ifdef SEAICE_DYN_STABLE_ADJOINT
202     cgf zero out adjoint fields to stabilize pkg/seaice dyna. adjoint
203     CALL ZERO_ADJ( 1, e11Loc, myThid)
204     CALL ZERO_ADJ( 1, e12Loc, myThid)
205     CALL ZERO_ADJ( 1, e22Loc, myThid)
206     #endif
207     #endif /* ALLOW_AUTODIFF_TAMC */
208    
209 mlosch 1.1 #endif /* SEAICE_ALLOW_DYNAMICS */
210     #endif /* SEAICE_CGRID */
211     RETURN
212     END

  ViewVC Help
Powered by ViewVC 1.1.22