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

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

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


Revision 1.22 - (show annotations) (download)
Wed Mar 18 10:26:10 2009 UTC (15 years, 2 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61k
Changes since 1.21: +1 -12 lines
removed superfluous many metric terms of FV discretization
of stress divergence for non-evp solver
(this part is not tested anywhere)

1 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_ocean_stress.F,v 1.21 2008/01/17 23:18:39 dimitri Exp $
2 C $Name: $
3
4 #include "SEAICE_OPTIONS.h"
5
6 CStartOfInterface
7 SUBROUTINE SEAICE_OCEAN_STRESS(
8 I myTime, myIter, myThid )
9 C /==========================================================\
10 C | SUBROUTINE SEAICE_OCEAN_STRESS |
11 C | o Calculate ocean surface stresses |
12 C | - C-grid version |
13 C |==========================================================|
14 C \==========================================================/
15 IMPLICIT NONE
16
17 C === Global variables ===
18 #include "SIZE.h"
19 #include "EEPARAMS.h"
20 #include "PARAMS.h"
21 #include "DYNVARS.h"
22 #include "GRID.h"
23 #include "FFIELDS.h"
24 #include "SEAICE.h"
25 #include "SEAICE_PARAMS.h"
26
27 C === Routine arguments ===
28 C myTime - Simulation time
29 C myIter - Simulation timestep number
30 C myThid - Thread no. that called this routine.
31 _RL myTime
32 INTEGER myIter
33 INTEGER myThid
34 CEndOfInterface
35
36 #ifdef SEAICE_CGRID
37 C === Local variables ===
38 C i,j,bi,bj - Loop counters
39
40 INTEGER i, j, bi, bj
41 _RL SINWAT, COSWAT, SINWIN, COSWIN
42 _RL fuIceLoc, fvIceLoc, FX, FY
43 _RL areaW, areaS
44
45 _RL e11 (1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
46 _RL e22 (1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
47 _RL e12 (1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
48 _RL press (1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
49 _RL sig11 (1-Olx:sNx+Olx,1-Oly:sNy+Oly)
50 _RL sig22 (1-Olx:sNx+Olx,1-Oly:sNy+Oly)
51 _RL sig12 (1-Olx:sNx+Olx,1-Oly:sNy+Oly)
52 _RL eplus, eminus
53
54 c introduce turning angle (default is zero)
55 SINWAT=SIN(SEAICE_waterTurnAngle*deg2rad)
56 COSWAT=COS(SEAICE_waterTurnAngle*deg2rad)
57 SINWIN=SIN(SEAICE_airTurnAngle*deg2rad)
58 COSWIN=COS(SEAICE_airTurnAngle*deg2rad)
59
60 IF ( useHB87StressCoupling ) THEN
61 C
62 C use an intergral over ice and ocean surface layer to define
63 C surface stresses on ocean following Hibler and Bryan (1987, JPO)
64 C
65 C recompute strain rates, viscosities, etc. from updated ice velocities
66 IF ( .NOT. SEAICEuseEVP ) THEN
67 C only for EVP we already have the stress components otherwise we need
68 C to recompute them here
69 CALL SEAICE_CALC_STRAINRATES(
70 I uIce, vIce,
71 O e11, e22, e12,
72 I 3, 3, myTime, myIter, myThid )
73
74 CALL SEAICE_CALC_VISCOSITIES(
75 I e11, e22, e12, zMin, zMax, hEffM, press0,
76 O eta, zeta, press,
77 I 3, myTime, myIter, myThid )
78 ENDIF
79 C re-compute internal stresses with updated ice velocities
80 DO bj=myByLo(myThid),myByHi(myThid)
81 DO bi=myBxLo(myThid),myBxHi(myThid)
82 IF ( .NOT. SEAICEuseEVP ) THEN
83 C only for EVP we already have computed the stress divergences, for
84 C anything else we have to do it here
85 DO j=1-Oly,sNy+Oly
86 DO i=1-Olx,sNx+Olx
87 sig11(I,J) = 0. _d 0
88 sig22(I,J) = 0. _d 0
89 sig12(I,J) = 0. _d 0
90 ENDDO
91 ENDDO
92
93 DO j=0,sNy
94 DO i=0,sNx
95 eplus = e11(I,J,bi,bj) + e22(I,J,bi,bj)
96 eminus= e11(I,J,bi,bj) - e22(I,J,bi,bj)
97 sig11(I,J) = zeta(I,J,bi,bj)*eplus + eta(I,J,bi,bj)*eminus
98 & - 0.5 _d 0 * PRESS(I,J,bi,bj)
99 sig22(I,J) = zeta(I,J,bi,bj)*eplus - eta(I,J,bi,bj)*eminus
100 & - 0.5 _d 0 * PRESS(I,J,bi,bj)
101 ENDDO
102 ENDDO
103
104 DO j=1,sNy+1
105 DO i=1,sNx+1
106 sig12(I,J) = 2. _d 0 * e12(I,J,bi,bj) *
107 & ( eta(I,J ,bi,bj) + eta(I-1,J ,bi,bj)
108 & + eta(I,J-1,bi,bj) + eta(I-1,J-1,bi,bj) )
109 & /MAX(1. _d 0,
110 & hEffM(I,J ,bi,bj) + hEffM(I-1,J ,bi,bj)
111 & + hEffM(I,J-1,bi,bj) + hEffM(I-1,J-1,bi,bj))
112 ENDDO
113 ENDDO
114 C evaluate divergence of stress and apply to forcing
115 DO J=1,sNy
116 DO I=1,sNx
117 FX = ( sig11(I ,J ) * _dyF(I ,J ,bi,bj)
118 & - sig11(I-1,J ) * _dyF(I-1,J ,bi,bj)
119 & + sig12(I ,J+1) * _dxV(I ,J+1,bi,bj)
120 & - sig12(I ,J ) * _dxV(I ,J ,bi,bj)
121 & ) * recip_rAw(I,J,bi,bj)
122 FY = ( sig22(I ,J ) * _dxF(I ,J ,bi,bj)
123 & - sig22(I ,J-1) * _dxF(I ,J-1,bi,bj)
124 & + sig12(I+1,J ) * _dyU(I+1,J ,bi,bj)
125 & - sig12(I ,J ) * _dyU(I ,J ,bi,bj)
126 & ) * recip_rAs(I,J,bi,bj)
127 C average wind stress over ice and ocean and apply averaged wind
128 C stress and internal ice stresses to surface layer of ocean
129 areaW = 0.5 * (AREA(I,J,1,bi,bj) + AREA(I-1,J,1,bi,bj))
130 & * SEAICEstressFactor
131 areaS = 0.5 * (AREA(I,J,1,bi,bj) + AREA(I,J-1,1,bi,bj))
132 & * SEAICEstressFactor
133 fu(I,J,bi,bj)=(ONE-areaW)*fu(I,J,bi,bj)
134 & + areaW*taux(I,J,bi,bj)
135 & + FX * SEAICEstressFactor
136 fv(I,J,bi,bj)=(ONE-areaS)*fv(I,J,bi,bj)
137 & + areaS*tauy(I,J,bi,bj)
138 & + FY * SEAICEstressFactor
139 C save stress divergence for later
140 #ifdef SEAICE_ALLOW_EVP
141 stressDivergenceX(I,J,bi,bj) = FX
142 stressDivergenceY(I,J,bi,bj) = FY
143 #endif /* SEAICE_ALLOW_EVP */
144 ENDDO
145 ENDDO
146 ELSE
147 #ifdef SEAICE_ALLOW_EVP
148 DO J=1,sNy
149 DO I=1,sNx
150 C average wind stress over ice and ocean and apply averaged wind
151 C stress and internal ice stresses to surface layer of ocean
152 areaW = 0.5 * (AREA(I,J,1,bi,bj) + AREA(I-1,J,1,bi,bj))
153 & * SEAICEstressFactor
154 areaS = 0.5 * (AREA(I,J,1,bi,bj) + AREA(I,J-1,1,bi,bj))
155 & * SEAICEstressFactor
156 fu(I,J,bi,bj)=(ONE-areaW)*fu(I,J,bi,bj)
157 & + areaW*taux(I,J,bi,bj)
158 & + stressDivergenceX(I,J,bi,bj) * SEAICEstressFactor
159 fv(I,J,bi,bj)=(ONE-areaS)*fv(I,J,bi,bj)
160 & + areaS*tauy(I,J,bi,bj)
161 & + stressDivergenceY(I,J,bi,bj) * SEAICEstressFactor
162 ENDDO
163 ENDDO
164 #endif /* SEAICE_ALLOW_EVP */
165 ENDIF
166 ENDDO
167 ENDDO
168
169 ELSE
170 C else: useHB87StressCoupling=F
171
172 C-- Compute ice-affected wind stress (interpolate to U/V-points)
173 C by averaging wind stress and ice-ocean stress according to
174 C ice cover
175 DO bj=myByLo(myThid),myByHi(myThid)
176 DO bi=myBxLo(myThid),myBxHi(myThid)
177 DO j=1,sNy
178 DO i=1,sNx
179 fuIceLoc=HALF*( DWATN(I,J,bi,bj)+DWATN(I-1,J,bi,bj) )*
180 & COSWAT *
181 & ( UICE(I,J,1,bi,bj)-uVel(I,J,1,bi,bj) )
182 & - SIGN(SINWAT, _fCori(I,J,bi,bj)) * 0.5 _d 0 *
183 & ( DWATN(I ,J,bi,bj) *
184 & 0.5 _d 0*(vIce(I ,J ,1,bi,bj)-vVel(I ,J ,1,bi,bj)
185 & +vIce(I ,J+1,1,bi,bj)-vVel(I ,J+1,1,bi,bj))
186 & + DWATN(I-1,J,bi,bj) *
187 & 0.5 _d 0*(vIce(I-1,J ,1,bi,bj)-vVel(I-1,J ,1,bi,bj)
188 & +vIce(I-1,J+1,1,bi,bj)-vVel(I-1,J+1,1,bi,bj))
189 & )
190 fvIceLoc=HALF*( DWATN(I,J,bi,bj)+DWATN(I,J-1,bi,bj) )*
191 & COSWAT *
192 & ( VICE(I,J,1,bi,bj)-vVel(I,J,1,bi,bj) )
193 & + SIGN(SINWAT, _fCori(I,J,bi,bj)) * 0.5 _d 0 *
194 & ( DWATN(I,J ,bi,bj) *
195 & 0.5 _d 0*(uIce(I ,J ,1,bi,bj)-uVel(I ,J ,1,bi,bj)
196 & +uIce(I+1,J ,1,bi,bj)-uVel(I+1,J ,1,bi,bj))
197 & + DWATN(I,J-1,bi,bj) *
198 & 0.5 _d 0*(uIce(I ,J-1,1,bi,bj)-uVel(I ,J-1,1,bi,bj)
199 & +uIce(I+1,J-1,1,bi,bj)-uVel(I+1,J-1,1,bi,bj))
200 & )
201 areaW = 0.5 _d 0 * (AREA(I,J,1,bi,bj) + AREA(I-1,J,1,bi,bj))
202 & * SEAICEstressFactor
203 areaS = 0.5 _d 0 * (AREA(I,J,1,bi,bj) + AREA(I,J-1,1,bi,bj))
204 & * SEAICEstressFactor
205 fu(I,J,bi,bj)=(ONE-areaW)*fu(I,J,bi,bj)+areaW*fuIceLoc
206 fv(I,J,bi,bj)=(ONE-areaS)*fv(I,J,bi,bj)+areaS*fvIceLoc
207 ENDDO
208 ENDDO
209 ENDDO
210 ENDDO
211 ENDIF
212 CALL EXCH_UV_XY_RS(fu, fv, .TRUE., myThid)
213
214 #endif /* SEAICE_CGRID */
215
216 RETURN
217 END

  ViewVC Help
Powered by ViewVC 1.1.22