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

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

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


Revision 1.22 - (hide annotations) (download)
Fri Oct 29 15:26:29 2010 UTC (13 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62n
Changes since 1.21: +9 -9 lines
fix typo in SEAICE_BICE_STRESS code

1 jmc 1.22 C $Header: /u/gcmpack/MITgcm/pkg/seaice/ostres.F,v 1.21 2009/06/24 08:23:00 mlosch Exp $
2 edhill 1.8 C $Name: $
3 heimbach 1.2
4     #include "SEAICE_OPTIONS.h"
5    
6     CStartOfInterface
7 mlosch 1.17 SUBROUTINE ostres( COR_ICE, myThid )
8 jmc 1.22 C *==========================================================*
9 heimbach 1.2 C | SUBROUTINE ostres |
10     C | o Calculate ocean surface stress |
11 jmc 1.22 C *==========================================================*
12     C *==========================================================*
13 heimbach 1.2 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 COR_ICE (1-OLx:sNx+OLx,1-OLy:sNy+OLy, nSx,nSy)
26     INTEGER myThid
27     CEndOfInterface
28    
29 mlosch 1.17 #ifndef SEAICE_CGRID
30 heimbach 1.2 C === Local variables ===
31 dimitri 1.4 C i,j,bi,bj - Loop counters
32 heimbach 1.2
33 dimitri 1.4 INTEGER i, j, bi, bj
34 heimbach 1.2 _RL SINWIN, COSWIN, SINWAT, COSWAT
35 mlosch 1.19 #ifdef SEAICE_BICE_STRESS
36 mlosch 1.14 _RL fuIce, fvIce
37     #endif
38 heimbach 1.2
39 mlosch 1.15 c introduce turning angle (default is zero)
40 mlosch 1.16 SINWIN=SIN(SEAICE_airTurnAngle*deg2rad)
41     COSWIN=COS(SEAICE_airTurnAngle*deg2rad)
42     SINWAT=SIN(SEAICE_waterTurnAngle*deg2rad)
43     COSWAT=COS(SEAICE_waterTurnAngle*deg2rad)
44 heimbach 1.2
45 dimitri 1.11 #ifdef SEAICE_ORIGINAL_BAD_ICE_STRESS
46 jmc 1.22 These lines are put here on purpose to cause the compilation
47 mlosch 1.20 to fail because the following code is retired and can no longer
48     be used. It was probably never used anyway.
49     CMLC-- Following formulation is problematic and is no longer used.
50     CML#ifdef SEAICE_ALLOW_DYNAMICS
51     CML IF ( SEAICEuseDYNAMICS ) THEN
52     CMLC-- Compute ice-affected wind stress
53     CML DO bj=myByLo(myThid),myByHi(myThid)
54     CML DO bi=myBxLo(myThid),myBxHi(myThid)
55     CML DO j=1,sNy
56     CML DO i=1,sNx
57     CML WINDX(I,J,bi,bj)=DWATN(I,J,bi,bj)
58 mlosch 1.21 CML & *(COSWAT*(GWATX(I,J,bi,bj)-UICE(I,J,bi,bj))
59 mlosch 1.20 CML & -SIGN(SINWAT,COR_ICE(I,J,bi,bj))
60     CML & *(GWATY(I,J,bi,bj)-VICEC(I,J,bi,bj)))
61     CML WINDY(I,J,bi,bj)=DWATN(I,J,bi,bj)
62     CML & *(SIGN(SINWAT,COR_ICE(I,J,bi,bj))
63     CML & *(GWATX(I,J,bi,bj)-UICEC(I,J,bi,bj))
64 mlosch 1.21 CML & +COSWAT*(GWATY(I,J,bi,bj)-VICE(I,J,bi,bj)))
65 mlosch 1.20 CML WINDX(I,J,bi,bj)=WINDX(I,J,bi,bj)-( COR_ICE(I,J,bi,bj)
66     CML & *GWATY(I,J,bi,bj)-COR_ICE(I,J,bi,bj)*VICEC(I,J,bi,bj))
67     CML WINDY(I,J,bi,bj)=WINDY(I,J,bi,bj)-(-COR_ICE(I,J,bi,bj)
68     CML & *GWATX(I,J,bi,bj)+COR_ICE(I,J,bi,bj)*UICEC(I,J,bi,bj))
69 mlosch 1.21 CML WINDX(I,J,bi,bj)=WINDX(I,J,bi,bj)-(UICE(I,J,bi,bj)
70 mlosch 1.20 CML & -UICE(I,J,3,bi,bj))*AMASS(I,J,bi,bj)/SEAICE_DT*TWO
71 mlosch 1.21 CML WINDY(I,J,bi,bj)=WINDY(I,J,bi,bj)-(VICE(I,J,bi,bj)
72 mlosch 1.20 CML & -VICE(I,J,3,bi,bj))*AMASS(I,J,bi,bj)/SEAICE_DT*TWO
73     CML ENDDO
74     CML ENDDO
75     CML ENDDO
76     CML ENDDO
77     CML DO bj=myByLo(myThid),myByHi(myThid)
78     CML DO bi=myBxLo(myThid),myBxHi(myThid)
79     CML DO j=1,sNy
80     CML DO i=1,sNx
81     CML WINDX(I,J,bi,bj)=-WINDX(I,J,bi,bj)
82     CML WINDY(I,J,bi,bj)=-WINDY(I,J,bi,bj)
83     CML ENDDO
84     CML ENDDO
85     CML ENDDO
86     CML ENDDO
87     CML ENDIF
88     CML#endif /* SEAICE_ALLOW_DYNAMICS */
89 dimitri 1.11 #endif /* SEAICE_ORIGINAL_BAD_ICE_STRESS */
90    
91 dimitri 1.3 C-- Update overlap regions
92 dimitri 1.9 CALL EXCH_UV_XY_RL(WINDX, WINDY, .TRUE., myThid)
93 heimbach 1.2
94 dimitri 1.10 #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 dimitri 1.7 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 heimbach 1.2 ENDDO
106     ENDDO
107     ENDDO
108     ENDDO
109 dimitri 1.9 CALL EXCH_UV_XY_RS(fu, fv, .TRUE., myThid)
110 dimitri 1.10 #endif /* ifndef SEAICE_EXTERNAL_FLUXES */
111 heimbach 1.2
112 mlosch 1.19 #ifdef SEAICE_BICE_STRESS
113 dimitri 1.11 C-- Compute ice-affected wind stress
114 dimitri 1.12 DO bj=myByLo(myThid),myByHi(myThid)
115     DO bi=myBxLo(myThid),myBxHi(myThid)
116     DO j=1,sNy
117     DO i=1,sNx
118 mlosch 1.16 fuIce=QUART*( DWATN(I,J,bi,bj)+DWATN(I,J+1,bi,bj) )*(
119 jmc 1.22 & COSWAT *
120 mlosch 1.21 & ( UICE(I,J, bi,bj)-GWATX(I,J, bi,bj)
121     & + UICE(I,J+1,bi,bj)-GWATX(I,J+1,bi,bj) )
122 mlosch 1.18 & -SIGN(SINWAT,COR_ICE(I,J,bi,bj)) *
123 mlosch 1.21 & ( VICE(I, J,bi,bj)-GWATY(I, J,bi,bj)
124     & + VICE(I+1,J,bi,bj)-GWATY(I+1,J,bi,bj) )
125 mlosch 1.16 & )
126     fvIce=QUART*( DWATN(I,J,bi,bj)+DWATN(I+1,J,bi,bj) )*(
127 jmc 1.22 & SIGN(SINWAT,COR_ICE(I,J,bi,bj)) *
128 mlosch 1.21 & ( UICE(I,J, bi,bj)-GWATX(I,J, bi,bj)
129     & + UICE(I,J+1,bi,bj)-GWATX(I,J+1,bi,bj) )
130 jmc 1.22 & + COSWAT *
131     & ( VICE(I, J,bi,bj)-GWATY(I, J,bi,bj)
132 mlosch 1.21 & + VICE(I+1,J,bi,bj)-GWATY(I+1,J,bi,bj) )
133 mlosch 1.16 & )
134 mlosch 1.21 fu(I,J,bi,bj)=(ONE-AREA(I,J,bi,bj))*fu(I,J,bi,bj)+
135     & AREA(I,J,bi,bj)*fuIce
136     fv(I,J,bi,bj)=(ONE-AREA(I,J,bi,bj))*fv(I,J,bi,bj)+
137     & AREA(I,J,bi,bj)*fvIce
138 dimitri 1.11 ENDDO
139     ENDDO
140     ENDDO
141 dimitri 1.12 ENDDO
142 dimitri 1.11 CALL EXCH_UV_XY_RS(fu, fv, .TRUE., myThid)
143 mlosch 1.19 #endif /* SEAICE_BICE_STRESS */
144 mlosch 1.17 #endif /* not SEAICE_CGRID */
145 dimitri 1.11
146 heimbach 1.2 RETURN
147     END

  ViewVC Help
Powered by ViewVC 1.1.22