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

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

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


Revision 1.14 - (show annotations) (download)
Tue Feb 7 08:08:28 2006 UTC (18 years, 4 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint58a_post
Changes since 1.13: +12 -9 lines
change the content of SEAICE_TEST_ICE_STRESS_1 into something that
make a little more sense than the previous version

1 C $Header: /u/gcmpack/MITgcm/pkg/seaice/ostres.F,v 1.13 2004/12/27 20:34:11 dimitri Exp $
2 C $Name: $
3
4 #include "SEAICE_OPTIONS.h"
5
6 CStartOfInterface
7 SUBROUTINE ostres( DWATN, COR_ICE, myThid )
8 C /==========================================================\
9 C | SUBROUTINE ostres |
10 C | o Calculate ocean surface stress |
11 C |==========================================================|
12 C \==========================================================/
13 IMPLICIT NONE
14
15 C === Global variables ===
16 #include "SIZE.h"
17 #include "EEPARAMS.h"
18 #include "PARAMS.h"
19 #include "FFIELDS.h"
20 #include "SEAICE.h"
21 #include "SEAICE_PARAMS.h"
22
23 C === Routine arguments ===
24 C myThid - Thread no. that called this routine.
25 _RL DWATN (1-OLx:sNx+OLx,1-OLy:sNy+OLy, nSx,nSy)
26 _RL COR_ICE (1-OLx:sNx+OLx,1-OLy:sNy+OLy, nSx,nSy)
27 INTEGER myThid
28 CEndOfInterface
29
30 C === Local variables ===
31 C i,j,bi,bj - Loop counters
32
33 INTEGER i, j, bi, bj
34 _RL SINWIN, COSWIN, SINWAT, COSWAT
35 #ifdef SEAICE_TEST_ICE_STRESS_1
36 _RL fuIce, fvIce
37 #endif
38
39 C 25 DEG GIVES SIN EQUAL TO 0.4226
40 SINWIN=0.4226 _d 0
41 COSWIN=0.9063 _d 0
42 SINWAT=0.4226 _d 0
43 COSWAT=0.9063 _d 0
44 c do not introduce turning angle
45 SINWIN=ZERO
46 COSWIN=ONE
47 SINWAT=ZERO
48 COSWAT=ONE
49
50 #ifdef SEAICE_ORIGINAL_BAD_ICE_STRESS
51 C-- Following formulation is problematic and is no longer used.
52 #ifdef SEAICE_ALLOW_DYNAMICS
53 IF ( SEAICEuseDYNAMICS ) THEN
54 C-- Compute ice-affected wind stress
55 DO bj=myByLo(myThid),myByHi(myThid)
56 DO bi=myBxLo(myThid),myBxHi(myThid)
57 DO j=1,sNy
58 DO i=1,sNx
59 WINDX(I,J,bi,bj)=DWATN(I,J,bi,bj)
60 & *(COSWAT*(GWATX(I,J,bi,bj)-UICE(I,J,1,bi,bj))
61 & -SINWAT*(GWATY(I,J,bi,bj)-VICEC(I,J,bi,bj)))
62 WINDY(I,J,bi,bj)=DWATN(I,J,bi,bj)
63 & *(SINWAT*(GWATX(I,J,bi,bj)-UICEC(I,J,bi,bj))
64 & +COSWAT*(GWATY(I,J,bi,bj)-VICE(I,J,1,bi,bj)))
65 WINDX(I,J,bi,bj)=WINDX(I,J,bi,bj)-( COR_ICE(I,J,bi,bj)
66 & *GWATY(I,J,bi,bj)-COR_ICE(I,J,bi,bj)*VICEC(I,J,bi,bj))
67 WINDY(I,J,bi,bj)=WINDY(I,J,bi,bj)-(-COR_ICE(I,J,bi,bj)
68 & *GWATX(I,J,bi,bj)+COR_ICE(I,J,bi,bj)*UICEC(I,J,bi,bj))
69 WINDX(I,J,bi,bj)=WINDX(I,J,bi,bj)-(UICE(I,J,1,bi,bj)
70 & -UICE(I,J,3,bi,bj))*AMASS(I,J,bi,bj)/SEAICE_DT*TWO
71 WINDY(I,J,bi,bj)=WINDY(I,J,bi,bj)-(VICE(I,J,1,bi,bj)
72 & -VICE(I,J,3,bi,bj))*AMASS(I,J,bi,bj)/SEAICE_DT*TWO
73 ENDDO
74 ENDDO
75 ENDDO
76 ENDDO
77 DO bj=myByLo(myThid),myByHi(myThid)
78 DO bi=myBxLo(myThid),myBxHi(myThid)
79 DO j=1,sNy
80 DO i=1,sNx
81 WINDX(I,J,bi,bj)=-WINDX(I,J,bi,bj)
82 WINDY(I,J,bi,bj)=-WINDY(I,J,bi,bj)
83 ENDDO
84 ENDDO
85 ENDDO
86 ENDDO
87 ENDIF
88 #endif /* SEAICE_ALLOW_DYNAMICS */
89 #endif /* SEAICE_ORIGINAL_BAD_ICE_STRESS */
90
91 C-- Update overlap regions
92 CALL EXCH_UV_XY_RL(WINDX, WINDY, .TRUE., myThid)
93
94 #ifndef SEAICE_EXTERNAL_FLUXES
95 C-- Interpolate wind stress (N/m^2) from South-West B-grid
96 C to South-West C-grid for forcing ocean model.
97 DO bj=myByLo(myThid),myByHi(myThid)
98 DO bi=myBxLo(myThid),myBxHi(myThid)
99 DO j=1,sNy
100 DO i=1,sNx
101 fu(I,J,bi,bj)=HALF
102 & *(WINDX(I,J+1,bi,bj)+WINDX(I,J,bi,bj))
103 fv(I,J,bi,bj)=HALF
104 & *(WINDY(I+1,J,bi,bj)+WINDY(I,J,bi,bj))
105 ENDDO
106 ENDDO
107 ENDDO
108 ENDDO
109 CALL EXCH_UV_XY_RS(fu, fv, .TRUE., myThid)
110 #endif /* ifndef SEAICE_EXTERNAL_FLUXES */
111
112 #ifdef SEAICE_TEST_ICE_STRESS_1
113 C-- Compute ice-affected wind stress
114 DO bj=myByLo(myThid),myByHi(myThid)
115 DO bi=myBxLo(myThid),myBxHi(myThid)
116 DO j=1,sNy
117 DO i=1,sNx
118 fuIce=QUART*( DWATN(I,J,bi,bj)+DWATN(I,J+1,bi,bj) )*
119 & ( UICE(I,J, 1,bi,bj)-GWATX(I,J, bi,bj)
120 & + UICE(I,J+1,1,bi,bj)-GWATX(I,J+1,bi,bj) )
121 fvIce=QUART*( DWATN(I,J,bi,bj)+DWATN(I+1,J,bi,bj) )*
122 & ( VICE(I, J,1,bi,bj)-GWATY(I, J,bi,bj)
123 & + VICE(I+1,J,1,bi,bj)-GWATY(I+1,J,bi,bj) )
124 fu(I,J,bi,bj)=(ONE-AREA(I,J,1,bi,bj))*fu(I,J,bi,bj)+
125 & AREA(I,J,1,bi,bj)*fuIce
126 fv(I,J,bi,bj)=(ONE-AREA(I,J,1,bi,bj))*fv(I,J,bi,bj)+
127 & AREA(I,J,1,bi,bj)*fvIce
128 ENDDO
129 ENDDO
130 ENDDO
131 ENDDO
132 CALL EXCH_UV_XY_RS(fu, fv, .TRUE., myThid)
133 #endif /* SEAICE_TEST_ICE_STRESS_1 */
134
135 RETURN
136 END

  ViewVC Help
Powered by ViewVC 1.1.22