/[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.26 - (hide annotations) (download)
Wed Jun 24 08:56:46 2009 UTC (14 years, 10 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s
Changes since 1.25: +16 -13 lines
cosmetic change: replace uVel(i,j,1,bi,bj) with uVel(i,j,kSrf,bi,bj)
etc.

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

  ViewVC Help
Powered by ViewVC 1.1.22