/[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.29 - (show annotations) (download)
Wed Nov 24 15:51:05 2010 UTC (13 years, 5 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62o, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.28: +2 -1 lines
forgot to add a comment explaining this absolutely absurd code change

1 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_ocean_stress.F,v 1.28 2010/11/24 15:36:31 mlosch 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 C kSrf - vertical index of surface layer
40 INTEGER i, j, bi, bj
41 INTEGER kSrf
42 _RL COSWAT
43 _RS SINWAT
44 _RL fuIceLoc, fvIceLoc
45 _RL areaW, areaS
46
47 C surrface level
48 kSrf = 1
49 C introduce turning angle (default is zero)
50 SINWAT=SIN(SEAICE_waterTurnAngle*deg2rad)
51 COSWAT=COS(SEAICE_waterTurnAngle*deg2rad)
52
53 IF ( useHB87StressCoupling ) THEN
54 C
55 C use an intergral over ice and ocean surface layer to define
56 C surface stresses on ocean following Hibler and Bryan (1987, JPO)
57 C
58 DO bj=myByLo(myThid),myByHi(myThid)
59 DO bi=myBxLo(myThid),myBxHi(myThid)
60 DO J=1,sNy
61 DO I=1,sNx
62 C average wind stress over ice and ocean and apply averaged wind
63 C stress and internal ice stresses to surface layer of ocean
64 areaW = 0.5 * (AREA(I,J,bi,bj) + AREA(I-1,J,bi,bj))
65 & * SEAICEstressFactor
66 fu(I,J,bi,bj)=(ONE-areaW)*fu(I,J,bi,bj)
67 & + areaW*taux(I,J,bi,bj)
68 & + stressDivergenceX(I,J,bi,bj) * SEAICEstressFactor
69 ENDDO
70 ENDDO
71 C This loop separation makes the adjoint code vectorize
72 DO J=1,sNy
73 DO I=1,sNx
74 areaS = 0.5 * (AREA(I,J,bi,bj) + AREA(I,J-1,bi,bj))
75 & * SEAICEstressFactor
76 fv(I,J,bi,bj)=(ONE-areaS)*fv(I,J,bi,bj)
77 & + areaS*tauy(I,J,bi,bj)
78 & + stressDivergenceY(I,J,bi,bj) * SEAICEstressFactor
79 ENDDO
80 ENDDO
81 ENDDO
82 ENDDO
83
84 ELSE
85 C else: useHB87StressCoupling=F
86
87 C-- Compute ice-affected wind stress (interpolate to U/V-points)
88 C by averaging wind stress and ice-ocean stress according to
89 C ice cover
90 DO bj=myByLo(myThid),myByHi(myThid)
91 DO bi=myBxLo(myThid),myBxHi(myThid)
92 DO j=1,sNy
93 DO i=1,sNx
94 fuIceLoc=HALF*( DWATN(I,J,bi,bj)+DWATN(I-1,J,bi,bj) )*
95 & COSWAT *
96 & ( uIce(I,J,bi,bj)-uVel(I,J,kSrf,bi,bj) )
97 & - SIGN(SINWAT, _fCori(I,J,bi,bj)) * 0.5 _d 0 *
98 & ( DWATN(I ,J,bi,bj) *
99 & 0.5 _d 0*(vIce(I ,J ,bi,bj)-vVel(I ,J ,kSrf,bi,bj)
100 & +vIce(I ,J+1,bi,bj)-vVel(I ,J+1,kSrf,bi,bj))
101 & + DWATN(I-1,J,bi,bj) *
102 & 0.5 _d 0*(vIce(I-1,J ,bi,bj)-vVel(I-1,J ,kSrf,bi,bj)
103 & +vIce(I-1,J+1,bi,bj)-vVel(I-1,J+1,kSrf,bi,bj))
104 & )
105 fvIceLoc=HALF*( DWATN(I,J,bi,bj)+DWATN(I,J-1,bi,bj) )*
106 & COSWAT *
107 & ( vIce(I,J,bi,bj)-vVel(I,J,kSrf,bi,bj) )
108 & + SIGN(SINWAT, _fCori(I,J,bi,bj)) * 0.5 _d 0 *
109 & ( DWATN(I,J ,bi,bj) *
110 & 0.5 _d 0*(uIce(I ,J ,bi,bj)-uVel(I ,J ,kSrf,bi,bj)
111 & +uIce(I+1,J ,bi,bj)-uVel(I+1,J ,kSrf,bi,bj))
112 & + DWATN(I,J-1,bi,bj) *
113 & 0.5 _d 0*(uIce(I ,J-1,bi,bj)-uVel(I ,J-1,kSrf,bi,bj)
114 & +uIce(I+1,J-1,bi,bj)-uVel(I+1,J-1,kSrf,bi,bj))
115 & )
116 areaW = 0.5 _d 0 * (AREA(I,J,bi,bj) + AREA(I-1,J,bi,bj))
117 & * SEAICEstressFactor
118 areaS = 0.5 _d 0 * (AREA(I,J,bi,bj) + AREA(I,J-1,bi,bj))
119 & * SEAICEstressFactor
120 fu(I,J,bi,bj)=(ONE-areaW)*fu(I,J,bi,bj)+areaW*fuIceLoc
121 fv(I,J,bi,bj)=(ONE-areaS)*fv(I,J,bi,bj)+areaS*fvIceLoc
122 ENDDO
123 ENDDO
124 ENDDO
125 ENDDO
126 ENDIF
127 CALL EXCH_UV_XY_RS(fu, fv, .TRUE., myThid)
128
129 #endif /* SEAICE_CGRID */
130
131 RETURN
132 END

  ViewVC Help
Powered by ViewVC 1.1.22