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

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

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


Revision 1.23 - (hide annotations) (download)
Fri May 29 10:18:03 2009 UTC (14 years, 11 months ago) by mlosch
Branch: MAIN
Changes since 1.22: +1 -5 lines
  - turn strain rates eij and press into global fields within global
    common block in SEAICE.h for more straighforward diagnostics

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

  ViewVC Help
Powered by ViewVC 1.1.22